From: Marcus Breiing
Subject: Function object equality
Date: 
Message-ID: <et5jiup8fibv5@breiing.com>
Given this definition:

(defun mkfoo (x)
  (labels ((foo ()
             (values #'foo x)))
    #'foo))

would you expect this

(let ((foo (mkfoo "...")))
  (eql (funcall foo)
       (funcall foo)))

to always return true?

(Asking because I accidentally noticed that CMUCL 19a returns NIL.)

-- 
Marcus Breiing

From: Peter Seibel
Subject: Re: Function object equality
Date: 
Message-ID: <m24q1q398m.fsf@gigamonkeys.com>
Marcus Breiing <······@2006w12.mail.breiing.com> writes:

> Given this definition:
>
> (defun mkfoo (x)
>   (labels ((foo ()
>              (values #'foo x)))
>     #'foo))
>
> would you expect this
>
> (let ((foo (mkfoo "...")))
>   (eql (funcall foo)
>        (funcall foo)))
>
> to always return true?

I would.

> (Asking because I accidentally noticed that CMUCL 19a returns NIL.)

Strange. Does it require the (VALUES ...) to get that result. I.e.
what happens if you simplify it to:

  (defun mkfoo () (labels ((foo () #'foo)) #'foo))

-Peter

-- 
Peter Seibel           * ·····@gigamonkeys.com
Gigamonkeys Consulting * http://www.gigamonkeys.com/
Practical Common Lisp  * http://www.gigamonkeys.com/book/
From: Marcus Breiing
Subject: Re: Function object equality
Date: 
Message-ID: <og5x5zq7aruh3@breiing.com>
* Peter Seibel

> Strange. Does it require the (VALUES ...) to get that result. I.e.
> what happens if you simplify it to:

>   (defun mkfoo () (labels ((foo () #'foo)) #'foo))

In that case, I get the "expected" behavior. (The relevant difference
doesn't seem to be the VALUES, but the closing-over-x. I returned x as
a second value to keep that from being optimized away.)

-- 
Marcus Breiing
From: Frode Vatvedt Fjeld
Subject: Re: Function object equality
Date: 
Message-ID: <2h3bhapiz9.fsf@vserver.cs.uit.no>
> * Peter Seibel
> 
> > Strange. Does it require the (VALUES ...) to get that result. I.e.
> > what happens if you simplify it to:
> 
> >   (defun mkfoo () (labels ((foo () #'foo)) #'foo))

Marcus Breiing <······@2006w12.mail.breiing.com> writes:

> In that case, I get the "expected" behavior. (The relevant
> difference doesn't seem to be the VALUES, but the closing-over-x. I
> returned x as a second value to keep that from being optimized
> away.)

This is precisely the behavior I'd expect to see. When x is closed
over, the value of #'foo must hold a reference to a particular binding
which is unique for that lexical scope. A second #'foo must hold a
reference to another binding, so the two can hardly be eq.

-- 
Frode Vatvedt Fjeld
From: Marcin 'Qrczak' Kowalczyk
Subject: Re: Function object equality
Date: 
Message-ID: <87wtempioa.fsf@qrnik.zagroda>
Frode Vatvedt Fjeld <······@cs.uit.no> writes:

> This is precisely the behavior I'd expect to see. When x is closed
> over, the value of #'foo must hold a reference to a particular
> binding which is unique for that lexical scope. A second #'foo must
> hold a reference to another binding, so the two can hardly be eq.

But there should be only one foo, as mkfoo is called only once.

-- 
   __("<         Marcin Kowalczyk
   \__/       ······@knm.org.pl
    ^^     http://qrnik.knm.org.pl/~qrczak/
From: Frode Vatvedt Fjeld
Subject: Re: Function object equality
Date: 
Message-ID: <2hy7z2o2lb.fsf@vserver.cs.uit.no>
Marcin 'Qrczak' Kowalczyk <······@knm.org.pl> writes:

> But there should be only one foo, as mkfoo is called only once.

Right you are, I read the original post too quickly. I suspect it's a
corner case in a compiler that is easy to miss.

-- 
Frode Vatvedt Fjeld
From: Rob Warnock
Subject: Re: Function object equality
Date: 
Message-ID: <DOadnbm3R9YHZbzZRVn-sQ@speakeasy.net>
Frode Vatvedt Fjeld  <······@cs.uit.no> wrote:
+---------------
| Marcin 'Qrczak' Kowalczyk <······@knm.org.pl> writes:
| > But there should be only one foo, as mkfoo is called only once.
| 
| Right you are, I read the original post too quickly. I suspect it's a
| corner case in a compiler that is easy to miss.
+---------------

Actually, it would seem that in CMUCL (nothing just 19c) that the 
FUNCTION special operator result in "executable code" (if you will)
that creates a closure at the moment the FUNCTION form is "executed".
And that in the OP's test code, the optimizer is not *quite* smart
enough to realize that the original #'FOO can be re-used. Here's the
OP's case, with MKFOO compiled [simplifies printouts]:

    cmu> (defun mkfoo (x)
	   (labels ((foo ()
		      (values (function foo) x)))
	     (function foo)))

    MKFOO
    cmu> (compile 'mkfoo)
    ; Compiling LAMBDA (X): 
    ; Compiling Top-Level Form: 

    MKFOO
    NIL
    NIL
    cmu> (deflex foo (mkfoo "xyz"))	; Pardon my DEFLEX...  ;-}

    FOO
    cmu> (funcall foo)

    #<Closure Over Function (LABELS FOO
			      MKFOO)
      {5890B689}>
    "xyz"
    cmu> (funcall foo)

    #<Closure Over Function (LABELS FOO
			      MKFOO)
      {5890C001}>
    "xyz"
    cmu> 

And a (DISASSEMBLE FOO) reveals that the (FUNCTION FOO) in the VALUES
call *is* allocating a new closure object (size = 16 bytes) inline:

      ...
      87:     MOV     EDX, 16
      8C:     ADD     EDX, [#x2800057C] ; X86::*CURRENT-REGION-FREE-POINTER*
      92:     CMP     EDX, [#x28000594] ; X86::*CURRENT-REGION-END-ADDR*
      98:     JBE     L0
      9A:     CALL    #xBE000010        ; #xBE000010: alloc_overflow_edx
      9F: L0: XCHG    EDX, [#x2800057C] ; X86::*CURRENT-REGION-FREE-POINTER*
      A5:     LEA     EDX, [EDX+1]
      A8:     MOV     DWORD PTR [EDX-1], 642
      ...fill in rest of struct & return...

The "+1" offset gives it a function pointer low-tag. The "642" (#x282)
is a header word for a "type_ClosureHeader" (#x82) with two additional
data words, a function (#'FOO itself) and a single closed-over value
[the string "xyz", as it happens in this case]:

     cmu> (dump32 (1- (kernel:get-lisp-obj-address foo)) 12)
     #x58964E60: #x00000282 #x5895C960 #x58962127
     cmu> (dump32 (1- (kernel:get-lisp-obj-address (funcall foo))) 12)
     #x589AFD20: #x00000282 #x5895C960 #x58962127
     cmu> (dump32 (1- (kernel:get-lisp-obj-address (funcall foo))) 12)
     #x589B5B00: #x00000282 #x5895C960 #x58962127
     cmu> (kernel:make-lisp-obj #x58962127)

     "xyz"
     cmu> 

As you can see, the *contents* of all three closure objects are entirely
the same, but they are still very different objects (in the EQ sense).

A slight tweak to MKFOO to avoid run-time creation of a closure makes
the "problem"(?) go away:

    cmu> (defun mkfoo (x)
	   (let ((foo nil))
	     (labels ((foo ()
			(values foo x)))
	       (setf foo (function foo)))))
    cmu> (compile *)

    ; Compiling LAMBDA (X): 
    ; Compiling Top-Level Form: 

    MKFOO
    NIL
    NIL
    cmu> (deflex foo (mkfoo "abc"))

    FOO
    cmu> (funcall foo)

    #<Closure Over Function (LABELS FOO
			      MKFOO)
      {589D2F81}>
    "abc"
    cmu> (funcall foo)

    #<Closure Over Function (LABELS FOO
			      MKFOO)
      {589D2F81}>
    "abc"
    cmu> (dump32 (1- (kernel:get-lisp-obj-address foo)) 12)
    #x589D2F80: #x00000382 #x589CAB88 #x589D2F7F
    cmu> (dump32 (1- (kernel:get-lisp-obj-address (funcall foo))) 12)
    #x589D2F80: #x00000382 #x589CAB88 #x589D2F7F
    cmu> (dump32 (1- (kernel:get-lisp-obj-address (funcall foo))) 12)
    #x589D2F80: #x00000382 #x589CAB88 #x589D2F7F
    cmu> 

To reprise the OP's test [well, with EQ instead of EQL]:

    cmu> (let ((foo (mkfoo "defghi")))
	   (eq foo (funcall foo)))

    T
    cmu> 


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Rob Warnock
Subject: Re: Function object equality
Date: 
Message-ID: <DOadnbi3R9aeZ7zZRVn-sQ@speakeasy.net>
Oops! I just wrote:
+---------------
| Actually, it would seem that in CMUCL (nothing just 19c) that...
+---------------

Sorry for the typo: It should have read "in CMUCL (not just 19c)",
that is, in all versions I have access to (back to 18e at least).


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Marcus Breiing
Subject: Re: Function object equality
Date: 
Message-ID: <gv9lcvd4et3a2@breiing.com>
* Rob Warnock

> Actually, it would seem that in CMUCL (nothing just 19c) that the 
> FUNCTION special operator result in "executable code" (if you will)
> that creates a closure at the moment the FUNCTION form is "executed".
> And that in the OP's test code, the optimizer is not *quite* smart
> enough to realize that the original #'FOO can be re-used. 

The optimizer seems to be in denial:

(defun strange (f)
  (flet ((foo () f))
    (let ((a #'foo)
          (b #'foo))
    (values
     (funcall f a b)
     (eq a b)))))


CL-USER> (strange #'eq)
NIL
T

SBCL 0.8.7 (the only version I have around) does it, too.

-- 
Marcus Breiing
From: Christophe Rhodes
Subject: Re: Function object equality
Date: 
Message-ID: <sqd5gdk515.fsf@cam.ac.uk>
Marcus Breiing <······@2006w12.mail.breiing.com> writes:

> CL-USER> (strange #'eq)
> NIL
> T
>
> SBCL 0.8.7 (the only version I have around) does it, too.

It was fixed in sbcl-0.8.19.

Christophe
From: Thomas F. Burdick
Subject: Re: Function object equality
Date: 
Message-ID: <xcvodzxjkx8.fsf@conquest.OCF.Berkeley.EDU>
Marcus Breiing <······@2006w12.mail.breiing.com> writes:

> Given this definition:
> 
> (defun mkfoo (x)
>   (labels ((foo ()
>              (values #'foo x)))
>     #'foo))
> 
> would you expect this
> 
> (let ((foo (mkfoo "...")))
>   (eql (funcall foo)
>        (funcall foo)))
> 
> to always return true?
> 
> (Asking because I accidentally noticed that CMUCL 19a returns NIL.)

It may not be what you expected, but by my reading, it's okay by the
spec due to this wording in the description of the FUNCTION special
operator:

  In situations where a closure over the same set of bindings might be
  produced more than once, the various resulting closures might or
  might not be eq.

By it's placement in the text it looks like it may have been intended
to refer to lambda expressions only -- LABELS can certainly create
lexical closures as defined in the glossary.

-- 
           /|_     .-----------------------.                        
         ,'  .\  / | Free Mumia Abu-Jamal! |
     ,--'    _,'   | Abolish the racist    |
    /       /      | death penalty!        |
   (   -.  |       `-----------------------'
   |     ) |                               
  (`-.  '--.)                              
   `. )----'                               
From: Marcin 'Qrczak' Kowalczyk
Subject: Re: Function object equality
Date: 
Message-ID: <87zmjhqibs.fsf@qrnik.zagroda>
···@conquest.OCF.Berkeley.EDU (Thomas F. Burdick) writes:

> It may not be what you expected, but by my reading, it's okay by the
> spec due to this wording in the description of the FUNCTION special
> operator:
>
>   In situations where a closure over the same set of bindings might be
>   produced more than once, the various resulting closures might or
>   might not be eq.

I disagree. This wording means that e.g. with (defun f (x) #'(lambda () x)),
the result of (eq (f 0) (f 0)) is unspecified. But in our case the closure
is logically created only once, not more than once.

-- 
   __("<         Marcin Kowalczyk
   \__/       ······@knm.org.pl
    ^^     http://qrnik.knm.org.pl/~qrczak/
From: Thomas F. Burdick
Subject: Re: Function object equality
Date: 
Message-ID: <xcvk6akjbu5.fsf@conquest.OCF.Berkeley.EDU>
Marcin 'Qrczak' Kowalczyk <······@knm.org.pl> writes:

> ···@conquest.OCF.Berkeley.EDU (Thomas F. Burdick) writes:
> 
> > It may not be what you expected, but by my reading, it's okay by the
> > spec due to this wording in the description of the FUNCTION special
> > operator:
> >
> >   In situations where a closure over the same set of bindings might be
> >   produced more than once, the various resulting closures might or
> >   might not be eq.
> 
> I disagree. This wording means that e.g. with (defun f (x) #'(lambda () x)),
> the result of (eq (f 0) (f 0)) is unspecified. But in our case the closure
> is logically created only once, not more than once.

No, what you're demonstrating is two closures over two different
bindings, which both happen to be binding the same value.  Those are
*required* to be different closures.  Eg:

  (defun f (x) (lambda (&optional y) (if y (setf x y) x)))
  (eq (f 0) (f 0)) ==must==> nil

An example of the situation referred to above would be:

  (defun f (x)
    (labels ((make-closure () (lambda () x)))
      (list (make-closure) (make-closure))))

*That* could result in:

  (apply #'eq (f 0)) ==> t
                     or
                     ==> nil

-- 
           /|_     .-----------------------.                        
         ,'  .\  / | Free Mumia Abu-Jamal! |
     ,--'    _,'   | Abolish the racist    |
    /       /      | death penalty!        |
   (   -.  |       `-----------------------'
   |     ) |                               
  (`-.  '--.)                              
   `. )----'                               
From: Marcin 'Qrczak' Kowalczyk
Subject: Re: Function object equality
Date: 
Message-ID: <871wwr5yio.fsf@qrnik.zagroda>
···@conquest.OCF.Berkeley.EDU (Thomas F. Burdick) writes:

>> I disagree. This wording means that e.g. with (defun f (x) #'(lambda () x)),
>> the result of (eq (f 0) (f 0)) is unspecified. But in our case the closure
>> is logically created only once, not more than once.
>
> No, what you're demonstrating is two closures over two different
> bindings, which both happen to be binding the same value.  Those are
> *required* to be different closures.

I'm not sure: you can't mutate *these* bindings, so unless there is
some explicit requirement about distinguishing otherwise equivalently
behaving functions, they don't seem to be required to be different.

-- 
   __("<         Marcin Kowalczyk
   \__/       ······@knm.org.pl
    ^^     http://qrnik.knm.org.pl/~qrczak/
From: Thomas F. Burdick
Subject: Re: Function object equality
Date: 
Message-ID: <xcvfyl7jx1p.fsf@conquest.OCF.Berkeley.EDU>
Marcin 'Qrczak' Kowalczyk <······@knm.org.pl> writes:

> ···@conquest.OCF.Berkeley.EDU (Thomas F. Burdick) writes:
> 
> >> I disagree. This wording means that e.g. with (defun f (x) #'(lambda () x)),
> >> the result of (eq (f 0) (f 0)) is unspecified. But in our case the closure
> >> is logically created only once, not more than once.
> >
> > No, what you're demonstrating is two closures over two different
> > bindings, which both happen to be binding the same value.  Those are
> > *required* to be different closures.
> 
> I'm not sure: you can't mutate *these* bindings, so unless there is
> some explicit requirement about distinguishing otherwise equivalently
> behaving functions, they don't seem to be required to be different.

I'm not sure that a compiler wouldn't be allowed to coalece two
closures over different, non-mutable bindings of the same value.  BUT,
that doesn't change the fact that they're different bindings.
Bindings and values are apples and oranges, my example with mutation
was merely to point out that fact.

(And have you thought about what a weird ass thing it would be for a
compiler to do what you're suggesting?  It would have to compile into
*every piece* of closure-generating code that produces closures that
don't mutate their bindigns -- for all instances of this precise
situation, it would have to insert code to look up a memoized value
for the closure closing over bindings with the given set of values.
This is not a reasonable thing.  *Maybe* conforming, much like a
hypothetical Lisp that has no GC, but not reasonable.)

But, getting back to the original point: for a closure over one set of
bindings (not values), FUNCTION may return a different value when
evaluated multiple times.

-- 
           /|_     .-----------------------.                        
         ,'  .\  / | Free Mumia Abu-Jamal! |
     ,--'    _,'   | Abolish the racist    |
    /       /      | death penalty!        |
   (   -.  |       `-----------------------'
   |     ) |                               
  (`-.  '--.)                              
   `. )----'                               
From: David Sletten
Subject: Re: Function object equality
Date: 
Message-ID: <UI_Uf.9491$WK1.2595@tornado.socal.rr.com>
Thomas F. Burdick wrote:

> Marcin 'Qrczak' Kowalczyk <······@knm.org.pl> writes:
> 
> 
>>···@conquest.OCF.Berkeley.EDU (Thomas F. Burdick) writes:
>>
>>
>>>>I disagree. This wording means that e.g. with (defun f (x) #'(lambda () x)),
>>>>the result of (eq (f 0) (f 0)) is unspecified. But in our case the closure
>>>>is logically created only once, not more than once.
>>>
>>>No, what you're demonstrating is two closures over two different
>>>bindings, which both happen to be binding the same value.  Those are
>>>*required* to be different closures.
>>
>>I'm not sure: you can't mutate *these* bindings, so unless there is
>>some explicit requirement about distinguishing otherwise equivalently
>>behaving functions, they don't seem to be required to be different.
> 
> 
> I'm not sure that a compiler wouldn't be allowed to coalece two
> closures over different, non-mutable bindings of the same value.  BUT,
> that doesn't change the fact that they're different bindings.
> Bindings and values are apples and oranges, my example with mutation
> was merely to point out that fact.
> 
> (And have you thought about what a weird ass thing it would be for a
> compiler to do what you're suggesting?  It would have to compile into
> *every piece* of closure-generating code that produces closures that
> don't mutate their bindigns -- for all instances of this precise
> situation, it would have to insert code to look up a memoized value
> for the closure closing over bindings with the given set of values.
> This is not a reasonable thing.  *Maybe* conforming, much like a
> hypothetical Lisp that has no GC, but not reasonable.)
> 

Bearing your caveats about the difficulty in mind, CLHS does explicitly 
say this is possible:
http://www.lispworks.com/documentation/HyperSpec/Body/03_ad.htm
The result of the form



  (let ((funs '()))
    (dotimes (j 10)
      (let ((x 5))
        (push (function (lambda (z) (+ x z)))
             funs)))
    funs)

is a list of ten closure objects that might or might not be identical. A 
different binding of x is involved for each closure, but the bindings 
cannot be distinguished because their values are the same and immutable 
(there being no occurrence of setq on x). A compiler could internally 
transform the form to



  (let ((funs '()))
    (dotimes (j 10)
      (push (function (lambda (z) (+ 5 z)))
            funs))
   funs)

where the closures may be identical.


David Sletten