How to check object's identity?

Hi, I tried this in ghci:
Prelude> 1:2:[] == 1:2:[] True
Does this mean (:) return the same object on same input, or (==) is not for identity checking? If the later is true, how can I check two object is the *same* object? Thanks Jan -- jan=callcc{|jan|jan};jan.call(jan)

Hi Jan,
in functional programming there is no such thing as "identity" as we
understand the idea from OO.
There is only such as thing as "equality" though.
Günther
Am 03.01.2009, 16:28 Uhr, schrieb Xie Hanjian
Hi,
I tried this in ghci:
Prelude> 1:2:[] == 1:2:[] True
Does this mean (:) return the same object on same input, or (==) is not for identity checking? If the later is true, how can I check two object is the *same* object?
Thanks Jan
-- Erstellt mit Operas revolutionärem E-Mail-Modul: http://www.opera.com/mail/

2009/1/3 Xie Hanjian
Hi,
I tried this in ghci:
Prelude> 1:2:[] == 1:2:[] True
Does this mean (:) return the same object on same input,
Also, in functional programming, *every* function returns the same output for the same input. That's part of the definition of function. :-) Luke

* Luke Palmer
2009/1/3 Xie Hanjian
Hi,
I tried this in ghci:
Prelude> 1:2:[] == 1:2:[] True
Does this mean (:) return the same object on same input,
Also, in functional programming, *every* function returns the same output for the same input. That's part of the definition of function. :-)
This is true in Haskell, but may not true in Scheme (I guess also false in Lisp). In DrScheme:
(eq? (cons 1 2) (cons 1 2)) #f (equal? (cons 1 2) (cons 1 2)) #t
Although equal? treats the two as the *same*, they're different lists because if we modify one (e.g by set-car!) the other won't be affected. So here comes another question: when we say a function always give the same output for the same input, what the *same* means here? ídentity or equality? Thanks Jan
Luke
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- jan=callcc{|jan|jan};jan.call(jan)

2009/1/3 Xie Hanjian
* Luke Palmer
[2009-01-03 18:46:50 -0700]: 2009/1/3 Xie Hanjian
Hi,
I tried this in ghci:
Prelude> 1:2:[] == 1:2:[] True
Does this mean (:) return the same object on same input,
Also, in functional programming, *every* function returns the same output for the same input. That's part of the definition of function. :-)
This is true in Haskell, but may not true in Scheme (I guess also false in Lisp).
I, like many arrogant Haskellers, reject Scheme and other such impure languages as "functional". At least until I turn on my brain. So, revise the beginning of my statement to "Also, in *pure* functional programming, ..." Luke
In DrScheme:
(eq? (cons 1 2) (cons 1 2)) #f (equal? (cons 1 2) (cons 1 2)) #t
Although equal? treats the two as the *same*, they're different lists because if we modify one (e.g by set-car!) the other won't be affected.
So here comes another question: when we say a function always give the same output for the same input, what the *same* means here? ídentity or equality?
Thanks Jan
Luke
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- jan=callcc{|jan|jan};jan.call(jan)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Luke Palmer wrote:
I, like many arrogant Haskellers, reject Scheme and other such impure languages as "functional". At least until I turn on my brain.
If Haskell is functional, then so is Scheme - it's just that Scheme lets you use IORefs and the IO monad without going to nearly as much trouble. Anton

Although equal? treats the two as the *same*, they're different lists because if we modify one (e.g by set-car!) the other won't be affected.
So here comes another question: when we say a function always give the same output for the same input, what the *same* means here? ídentity or equality?
If you don't have set-car!, then identity and equality are impossible to differentiate. And haskell doesn't have set-car!. However, as was noted, it does have something like mutable pointers via IORef, and sure enough, you can do pointer comparisons with them: h <- newIORef 12 h' <- newIORef 12 print $ h == h --> True print $ h == h' --> False Since they're pointers, to compare by value you have to explicitly derefence them: print =<< liftM2 (==) (readIORef h) (readIORef h') --> True If you're wondering about the implementation of "(1:[], 1:[])", ghc might be smart enough to do CSE in this case and hence use the same memory for both lists, but in general CSE doesn't happen to avoid accidental recomputation. There's some stuff in the ghc manual about lambda and let lifting that describes when CSE will and won't happen. I wouldn't count on it in general, but I don't read core well enough to tell. Maybe someone who knows more about core can help me here: a = \ (eta_azv :: State# RealWorld) -> case a24 stdout lvl7 eta_azv of wild_aFu { (# new_s_aFw, a103_aFx #) -> $wa13 stdout '\n' new_s_aFw } There are lots of apparently undefined variables, like the function 'a24'. But it looks like the pair should come from 'lvl7', which is chained all the way down to 'lvl' like so: lvl :: Integer lvl = S# 1 lvl1 :: [Integer] lvl1 = : @ Integer lvl ([] @ Integer) lvl2 :: ShowS lvl2 = showList lvl1 lvl3 :: [ShowS] lvl3 = : @ ShowS lvl2 ([] @ ShowS) lvl4 :: [ShowS] lvl4 = : @ ShowS lvl2 lvl3 lvl5 :: [Char] lvl5 = : @ Char a2 ([] @ Char) lvl6 :: String lvl6 = foldr1 @ (String -> String) lvl16 lvl4 lvl5 lvl7 :: [Char] lvl7 = : @ Char a lvl6 So it *looks* like there's only one list created in 'lvl1', but I can't see where it's turning into a tuple, and I don't understand the ' = : ' stuff, as in 'lvl5 = : @ Char a2 ([] @ Char)'. 'lvl5' is a Char resulting from the application of 'a2' to ""? The code, btw, was 'main = print (1:[], 1:[])'.

On Sun, 2009-01-04 at 16:19 +0800, Evan Laforge wrote:
Although equal? treats the two as the *same*, they're different lists because if we modify one (e.g by set-car!) the other won't be affected.
So here comes another question: when we say a function always give the same output for the same input, what the *same* means here? ídentity or equality?
If you don't have set-car!, then identity and equality are impossible to differentiate. And haskell doesn't have set-car!.
However, as was noted, it does have something like mutable pointers via IORef, and sure enough, you can do pointer comparisons with them:
h <- newIORef 12 h' <- newIORef 12 print $ h == h --> True print $ h == h' --> False
Since they're pointers, to compare by value you have to explicitly derefence them:
print =<< liftM2 (==) (readIORef h) (readIORef h') --> True
If you're wondering about the implementation of "(1:[], 1:[])", ghc might be smart enough to do CSE in this case and hence use the same memory for both lists, but in general CSE doesn't happen to avoid accidental recomputation. There's some stuff in the ghc manual about lambda and let lifting that describes when CSE will and won't happen. I wouldn't count on it in general, but I don't read core well enough to tell. Maybe someone who knows more about core can help me here:
a = \ (eta_azv :: State# RealWorld) -> case a24 stdout lvl7 eta_azv of wild_aFu { (# new_s_aFw, a103_aFx #) -> $wa13 stdout '\n' new_s_aFw }
There are lots of apparently undefined variables, like the function 'a24'. But it looks like the pair should come from 'lvl7', which is chained all the way down to 'lvl' like so:
lvl :: Integer lvl = S# 1
lvl1 :: [Integer] lvl1 = : @ Integer lvl ([] @ Integer)
lvl2 :: ShowS lvl2 = showList lvl1
lvl3 :: [ShowS] lvl3 = : @ ShowS lvl2 ([] @ ShowS)
lvl4 :: [ShowS] lvl4 = : @ ShowS lvl2 lvl3
lvl5 :: [Char] lvl5 = : @ Char a2 ([] @ Char)
lvl6 :: String lvl6 = foldr1 @ (String -> String) lvl16 lvl4 lvl5
lvl7 :: [Char] lvl7 = : @ Char a lvl6
So it *looks* like there's only one list created in 'lvl1', but I can't see where it's turning into a tuple, and I don't understand the ' = : ' stuff,
You're reading it wrong. : is a name. It's lvl5 = (:) @ Char a2 ([] @ Char) where @ is type application (instantiation). Triming that, it's lvl5 = (:) a2 [] or just lvl5 = a2:[]

So it *looks* like there's only one list created in 'lvl1', but I can't see where it's turning into a tuple, and I don't understand the ' = : ' stuff,
You're reading it wrong. : is a name. It's lvl5 = (:) @ Char a2 ([] @ Char) where @ is type application (instantiation). Triming that, it's lvl5 = (:) a2 [] or just lvl5 = a2:[]
Ooohhhh, much clearer, thanks! The lack of ()s threw me. I'm still confused about the apparently undefined 'a2' though. However, it looks like there's only one [1], defined in lvl1, so I guess this means ghc has merged the two conses into one variable, and hence they really do have the same identity?

* Evan Laforge
Although equal? treats the two as the *same*, they're different lists because if we modify one (e.g by set-car!) the other won't be affected.
So here comes another question: when we say a function always give the same output for the same input, what the *same* means here? ídentity or equality?
If you don't have set-car!, then identity and equality are impossible to differentiate. And haskell doesn't have set-car!.
However, as was noted, it does have something like mutable pointers via IORef, and sure enough, you can do pointer comparisons with them:
h <- newIORef 12 h' <- newIORef 12 print $ h == h --> True print $ h == h' --> False
Since they're pointers, to compare by value you have to explicitly derefence them:
print =<< liftM2 (==) (readIORef h) (readIORef h') --> True
If you're wondering about the implementation of "(1:[], 1:[])", ghc might be smart enough to do CSE in this case and hence use the same memory for both lists, but in general CSE doesn't happen to avoid accidental recomputation. There's some stuff in the ghc manual about lambda and let lifting that describes when CSE will and won't happen. I wouldn't count on it in general, but I don't read core well enough to tell. Maybe someone who knows more about core can help me here:
Very clear explanation, thanks Evan :-) -- jan=callcc{|jan|jan};jan.call(jan)

On Sun, Jan 04, 2009 at 04:19:38PM +0800, Evan Laforge wrote:
If you don't have set-car!, then identity and equality are impossible to differentiate.
There's still eqv?. (I wish people wouldn't use eq? as an example of an identity-comparison operation. It's as underdefined as unsafePtrEq.) So although state implies identity, the converse is not true. You can also have immutable objects with distinct identities. Some dialects of Scheme have recently started leaning towards making pairs immutable, but whether they should also make them indistinguishable is a separate question: http://groups.google.com/group/comp.lang.scheme/browse_thread/thread/7eccba9... And having a limited form of observable identity has even been proposed for Haskell: http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.31.4053 Personally, I find the idea appealing (and have implemented the Refs in the paper with IORefs and unsafePerformIO), because really, even currently a programmer has to care about sharing since it can have radical implications for performance and memory usage. Making it observable in the program would just mean acknowledging the fact that in real-world programming, you can't _really_ replace a variable with its definition without changing its behavior in important ways. Lauri

Lauri Alanko
Personally, I find the idea appealing (and have implemented the Refs in the paper with IORefs and unsafePerformIO), because really, even currently a programmer has to care about sharing since it can have radical implications for performance and memory usage. Making it observable in the program would just mean acknowledging the fact that in real-world programming, you can't _really_ replace a variable with its definition without changing its behavior in important ways.
+1 realism. -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.

On Jan 3, 2009, at 7:28 AM, Xie Hanjian wrote:
Hi,
I tried this in ghci:
Prelude> 1:2:[] == 1:2:[] True
Does this mean (:) return the same object on same input, or (==) is not for identity checking? If the later is true, how can I check two object is the *same* object?
As others have explained, the == operator doesn't tell you whether two values are actually stored at the same location in memory. If you really need to do this, however, GHC does provide a primitive for comparing the addresses of two arbitrary values: reallyUnsafePtrEquality# :: a -> a -> Int# http://haskell.org/ghc/docs/latest/html/libraries/ghc-prim/GHC-Prim.html#22 Take note of the "reallyUnsafe" prefix, though. :-) It's not something most programs should ever need to deal with. Aaron

On 4 Jan 2009, at 18:08, Aaron Tomb wrote:
On Jan 3, 2009, at 7:28 AM, Xie Hanjian wrote:
Hi,
I tried this in ghci:
Prelude> 1:2:[] == 1:2:[] True
Does this mean (:) return the same object on same input, or (==) is not for identity checking? If the later is true, how can I check two object is the *same* object?
As others have explained, the == operator doesn't tell you whether two values are actually stored at the same location in memory. If you really need to do this, however, GHC does provide a primitive for comparing the addresses of two arbitrary values:
reallyUnsafePtrEquality# :: a -> a -> Int#
http://haskell.org/ghc/docs/latest/html/libraries/ghc-prim/GHC-Prim.html#22
Take note of the "reallyUnsafe" prefix, though. :-) It's not something most programs should ever need to deal with.
Of note, you probably don't need to do this. It's usually safer to associate data with a key, using Data.Map, or just pairing objects with a unique id. Bob

Aaron Tomb
As others have explained, the == operator doesn't tell you whether two values are actually stored at the same location in memory.
Nobody yet mentioned that (==) doesn't guarantee *anything* - it's a user defined function. So while it may and should give structural equality, it also may not. -k -- If I haven't seen further, it is by standing in the footprints of giants

Maybe you could use stable names for this:
http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Stable...
"Stable names are a way of performing fast (O(1)), not-quite-exact
comparison between objects. Stable names solve the following problem:
suppose you want to build a hash table with Haskell objects as keys,
but you want to use pointer equality for comparison; maybe because the
keys are large and hashing would be slow, or perhaps because the keys
are infinite in size. We can't build a hash table using the address of
the object as the key, because objects get moved around by the garbage
collector, meaning a re-hash would be necessary after every garbage
collection."
2009/1/3 Xie Hanjian
Hi,
I tried this in ghci:
Prelude> 1:2:[] == 1:2:[] True
Does this mean (:) return the same object on same input, or (==) is not for identity checking? If the later is true, how can I check two object is the *same* object?
Thanks Jan
-- jan=callcc{|jan|jan};jan.call(jan)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (13)
-
Aaron Tomb
-
Achim Schneider
-
Anton van Straaten
-
Derek Elkins
-
Evan Laforge
-
Günther Schmidt
-
jan.h.xie@gmail.com
-
Ketil Malde
-
Lauri Alanko
-
Luke Palmer
-
Peter Verswyvelen
-
Thomas Davie
-
Xie Hanjian