(Implicit) equality testing using multiple function definitions

Hi list! When I define an algebraic datatype without an instance for Eq, I'm obviously unable to use the (==) function on it. I can pattern-match with a series of function definitions (f [] = False; f x = True) on the expression, though. Why is that? I understand that in the second case I'm not literally using the (==) function, but it seems like there would be instances where you'd intentionally not want to be able to test for equality, and pattern-matching with multiple function definitions circumvents that. Thanks for your time, Tom

Pattern matching 'works' simply because all it does is what it
describes: it scrutinizes or 'matches' a value of a specific type
against a set constructors of that type.
The classic way to circumvent this is to put the datatype behind a
module, where only the type is exported, but none of the constructors
are exported:
-- Note the difference between the export 'Foo(..)' and just 'Foo' -
-- one exposes the type and all its constructors, the other exposes only
-- the type.
module HiddenType ( Foo, mySpecialEquality ) where
data Foo = Bar ... -- no 'deriving Eq'
-- a special, super secret equality function, so clients can't create
-- their own or try to.
mySpecialEquality :: Foo -> Foo -> Bool
mySpecialEquality = ...
module Main where
import Foo
-- this is invalid, as 'Bar' is not exported and thus not in scope, no
pattern matching allowed.
f :: Foo -> ...
f Bar = ...
More generally this kind of idiom is found when you deal with what you
call 'smart constructors' - functions which, like a constructor,
create a value of a specific data type. But instead of doing it via
the constructor itself, you make the type opaque, and export functions
that construct values in the sensible or correct way:
module Even (Even, makeFoo) where
-- the underlying Int should only be even
data Even = Even Int deriving (Eq, Show)
-- safe, smart constructor for the Even datatype
makeEven :: Int -> Maybe Even
makeEven x = if not (x `mod` 2 == 0) then Nothing else Just x
Hope it helps.
On Mon, Jul 18, 2011 at 7:44 PM, Tom Murphy
Hi list! When I define an algebraic datatype without an instance for Eq, I'm obviously unable to use the (==) function on it. I can pattern-match with a series of function definitions (f [] = False; f x = True) on the expression, though. Why is that? I understand that in the second case I'm not literally using the (==) function, but it seems like there would be instances where you'd intentionally not want to be able to test for equality, and pattern-matching with multiple function definitions circumvents that.
Thanks for your time, Tom
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Regards, Austin

19/07/2011 10:44 AM, Tom Murphy kirjutas:
Hi list! When I define an algebraic datatype without an instance for Eq, I'm obviously unable to use the (==) function on it. I can pattern-match with a series of function definitions (f [] = False; f x = True) on the expression, though. Why is that? I understand that in the second case I'm not literally using the (==) function, but it seems like there would be instances where you'd intentionally not want to be able to test for equality, and pattern-matching with multiple function definitions circumvents that.
My take on this (may not be canonical, or even right!) is that pattern matching is matching on the shape of the object. E.g. with the data type:
data Foo a = Bar a | Quux a
.. then it's not possible to stop someone matching on a Foo a to determine if it was constructed with Bar or Quux. If you couldn't know that, it'd be impossible to do .. well, anything at all with it. But Foo a isn't an Eq instance, even if a happens to be, because we haven't defined the rules by which that happens. Deriving Eq is an easy way to do that, but it simply may not make sense to do so. Pattern matching is a different beast to testing for equality. Though I have few good examples, you can't match on 'x' for an arbitrary 'x' at run-time: the shape has to be determined at compile-time. That means you can only use (nested) constructors, so e.g. you can't match the contents of a Data.Map. Cheers, Arlen

On Jul 18, 2011, at 9:05 PM, Arlen Cuss wrote:
My take on this (may not be canonical, or even right!) is that pattern matching is matching on the shape of the object.
Perhaps we could say that pattern matching implements Structural Induction rather than set equality.
____________________ David Place Owner, Panpipes Ho! LLC http://panpipesho.com d@vidplace.com

On Mon, Jul 18, 2011 at 20:44, Tom Murphy
Hi list! When I define an algebraic datatype without an instance for Eq, I'm obviously unable to use the (==) function on it. I can pattern-match with a series of function definitions (f [] = False; f x = True) on the expression, though. Why is that? I understand that in the second case I'm not literally using the (==) function, but it seems like there would be instances where you'd intentionally not want to be able to test for equality, and pattern-matching with multiple function definitions circumvents that.
(==) is about value comparison; pattern matching is about constructor comparison, which is on a higher semantic level as value equality is only meaningful within the same constructor. "Circumvents"? You make it sound like the point of typeclasses is to restrict things. In fact, the point is to *undo* the restrictions necessarily introduced by polymorphism: if you don't know the type of something, you don't know what you can do with it. Typeclasses let us say "this can be any type, but we need to be able to do <x> with it". They don't circumvent; they *add*. Are you approaching this from an OO perspective, where you can throw messages at anything and hope they stick? Haskell, ML, and similar languages are based on strong types: if you know the type, you know *everything* about its possible values. Dynamic message passing means you can send a message to an object that doesn't know what to do with it, producing a runtime error; the whole point of strong typing is to make using an operation not supported by a given type a *compile time* error. That is not to say there aren't hybrid systems (see O'Caml) or static strongly-typed OO systems (see research papers about OOHaskell; this hasn't been followed up directly, although it's the basis for a number of other research topics). But in general, the design of a Haskell or SML program is in designing types that reflect the problem space, such that (a) if you do something that isn't quite right, it is a compile-time error instead of a runtime error, and (b) the types of functions are themselves the solutions to the problems (that is, you would like the implementation for some function to be obvious from its type; when it isn't, this usually means some kind of dependent typing is going on, which Haskell can't express directly, or that you otherwise haven't actually captured the problem space with your types). -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On 7/18/11, Brandon Allbery
"Circumvents"? You make it sound like the point of typeclasses is to restrict things. In fact, the point is to *undo* the restrictions necessarily introduced by polymorphism: if you don't know the type of something, you don't know what you can do with it. Typeclasses let us say "this can be any type, but we need to be able to do <x> with it". They don't circumvent; they *add*.
I wish I could think of a good example. Since I can't, I'll just try and make my point: In a way, the point of typeclasses _is_ to restrict things: one of the things that typeclasses enables is a compile-time error if I, say, try and add Bools: by not giving Bool a Num instance, we're expressing that something can't be expressed. There has to be a reason why we've all typed "deriving (Eq)" again and again: because sometimes we don't want, for some OurType, to be able to express: (a :: OurType) == (b :: OurType). This is the source of my confusion. Thanks for your time, Tom

On Wed, Jul 20, 2011 at 14:38, Tom Murphy
There has to be a reason why we've all typed "deriving (Eq)" again and again: because sometimes we don't want, for some OurType, to be able to express: (a :: OurType) == (b :: OurType).
There is a good reason, but that's not it. You're still thinking in terms of objects that carry method dictionaries around; Haskell *is not object oriented*, values are just values. Operations are defined by types, not by values. You can't ask a value how it should be compared. Typeclasses, which superficially look like objects/classes but aren't, are a way around this. A typeclass actually defines a dictionary mapping types to functions; but because values are not objects, some way needs to be provided to pass these dictionaries where they are needed. This is the function of contexts: they're actually function arguments.
f :: Eq a => a -> a -> a
is a function that takes three arguments: a map of implementations, and two values of some type. Whenever this function is invoked, the compiler passes it the Eq dictionary entry for the appropriate type a. If there were multiple typeclass contexts, the map would combine all of them. It's not about hiding anything. The only reason you think there is something to hide is because an object would carry around that information and something would therefore have to hide it for it to not be available; but there are no objects here, so something has to be added to carry it around. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On Wed, Jul 20, 2011 at 02:38:39PM -0400, Tom Murphy wrote:
On 7/18/11, Brandon Allbery
wrote: [...] "Circumvents"? You make it sound like the point of typeclasses is to restrict things. In fact, the point is to *undo* the restrictions necessarily introduced by polymorphism: if you don't know the type of something, you don't know what you can do with it. Typeclasses let us say "this can be any type, but we need to be able to do <x> with it". They don't circumvent; they *add*.
I wish I could think of a good example. Since I can't, I'll just try and make my point: In a way, the point of typeclasses _is_ to restrict things: one of the things that typeclasses enables is a compile-time error if I, say, try and add Bools: by not giving Bool a Num instance, we're expressing that something can't be expressed.
I think you are both right. There's a duality here, depending on your point of view. Consider a function type blah :: Foo a => ... a ...
From the point of view of someone *calling* this function, the Foo constraint *adds* some restriction: you may only pass things whose type is an instance of Foo. If you try to pass anything else you will get an error.
From the point of view of someone *implementing* this function, the Foo constraint *removes* some restriction: if there was no Foo constraint you would not be able to do anything with any arguments of type 'a'; given the Foo constraint you can do anything you could have done without it, *plus* you can use any Foo methods.
-Brent

Hello! Trying to rewrite a program I ran into a type problem with typeclasses. It's a mini-interpreter, the essential (extremely reduced) part is: eval e k = case (car e) of (Id "begin") -> eval_begin (cdr e) k eval_begin e k = eval (car e) (if isNull (cdr e) then k else (BeginCont k (cdr e))) Using "data" to define my data all is well: data Continuation = BeginCont Continuation Expression resume k e = case k of BeginCont k' es -> eval_begin es k' Unfortunately when trying to extend the program by other types of "Continuation" I must add to the data definition and add a matching clause to "resume". That is I must modify the core module. So I tried to decouple this using a typeclass like so: class Continuation a where resume :: a -> Expression -> Expression data BeginCont a = BeginCont a Expression deriving (Show) instance (Continuation a) => Continuation (BeginCont a) where resume (BeginCont k es) v = eval_begin es k This, however, results in an "infinite type" error. Is there a way to make the typeclass version typecheck? If not: How can one decouple this code in Haskell? What also puzzles me are the differences in "infinite" types. The above data declaration for "Continuation" is essentially infinite, too. But it works. And I thought I had understood this part... Any hints greatly appreciated! Thanks in advance, Thomas PS: The minimal "program" to get it type check is: data Expression = Null | Num Int | Id String | List [Expression] deriving (Eq, Show) cdr :: Expression -> Expression cdr (List []) = error "cdr Null !" cdr (List (_:[])) = Null cdr (List (l:ls)) = List ls car :: Expression -> Expression car (List l) = head l isNull Null = True isNull _ = False eval e k = case (car e) of (Id "begin") -> eval_begin (cdr e) k eval_begin e k = eval (car e) (if isNull (cdr e) then k else (BeginCont k (cdr e))) -- replace the following 5 lines... data Continuation = BeginCont Continuation Expression resume k e = case k of BeginCont k' es -> eval_begin es k' {- ... with these to see the error class Continuation a where resume :: a -> Expression -> Expression data BeginCont a = BeginCont a Expression deriving (Show) instance (Continuation a) => Continuation (BeginCont a) where resume (BeginCont k es) v = eval_begin es k -]

On Jul 20, 2011, at 5:58 PM, Thomas wrote:
class Continuation a where resume :: a -> Expression -> Expression
data BeginCont a = BeginCont a Expression deriving (Show) instance (Continuation a) => Continuation (BeginCont a) where resume (BeginCont k es) v = eval_begin es k
I think we need to know the definition of Expression. if define it with a dummy type eval_begin a b = a type Expression = Int this code fragment compiles. Would you send a code fragment that will yield the error? ____________________ David Place Owner, Panpipes Ho! LLC http://panpipesho.com d@vidplace.com

Hello David! Thank you for taking the time. Here is a complete fragment that shows the error: data Expression = Null | Num Int | Id String | List [Expression] deriving (Eq, Show) cdr :: Expression -> Expression cdr (List []) = error "cdr Null !" cdr (List (_:[])) = Null cdr (List (l:ls)) = List ls car :: Expression -> Expression car (List l) = head l car n = error (show n) isNull Null = True isNull _ = False eval e k = case (car e) of (Id "begin") -> eval_begin (cdr e) k eval_begin e k = eval (car e) (if isNull (cdr e) then k else (BeginCont k (cdr e))) class Continuation a where resume :: a -> Expression -> Expression data BeginCont a = BeginCont a Expression deriving (Show) instance (Continuation a) => Continuation (BeginCont a) where resume (BeginCont k es) v = eval_begin es k Regards, Thomas On 21.07.2011 00:18, David Place wrote:
On Jul 20, 2011, at 5:58 PM, Thomas wrote:
class Continuation a where resume :: a -> Expression -> Expression
data BeginCont a = BeginCont a Expression deriving (Show) instance (Continuation a) => Continuation (BeginCont a) where resume (BeginCont k es) v = eval_begin es k
I think we need to know the definition of Expression. if define it with a dummy type
eval_begin a b = a type Expression = Int
this code fragment compiles. Would you send a code fragment that will yield the error? ____________________ David Place Owner, Panpipes Ho! LLC http://panpipesho.com d@vidplace.com

On Jul 20, 2011, at 6:26 PM, Thomas wrote:
Thank you for taking the time. Here is a complete fragment that shows the error:
Hi, Thomas. I'm very sympathetic. I hate it when I get an error like this. I looked at your code and the solution didn't jump off the page, maybe it will for someone else. In the meantime, I suggest this strategy. Carefully give type signatures to all of your functions. This way you can help the type checker give better error messages. The type inference algorithm can go away into crazy land if you give it a nonsense definition. ___________________ David Place Owner, Panpipes Ho! LLC http://panpipesho.com d@vidplace.com

Please disregard my previous message. I didn't read your message carefully enough. ____________________ David Place Owner, Panpipes Ho! LLC http://panpipesho.com d@vidplace.com On Jul 20, 2011, at 5:58 PM, Thomas wrote:
Hello!
Trying to rewrite a program I ran into a type problem with typeclasses.
It's a mini-interpreter, the essential (extremely reduced) part is:
eval e k = case (car e) of (Id "begin") -> eval_begin (cdr e) k eval_begin e k = eval (car e) (if isNull (cdr e) then k else (BeginCont k (cdr e)))
Using "data" to define my data all is well:
data Continuation = BeginCont Continuation Expression resume k e = case k of BeginCont k' es -> eval_begin es k'
Unfortunately when trying to extend the program by other types of "Continuation" I must add to the data definition and add a matching clause to "resume". That is I must modify the core module. So I tried to decouple this using a typeclass like so:
class Continuation a where resume :: a -> Expression -> Expression
data BeginCont a = BeginCont a Expression deriving (Show) instance (Continuation a) => Continuation (BeginCont a) where resume (BeginCont k es) v = eval_begin es k
This, however, results in an "infinite type" error.
Is there a way to make the typeclass version typecheck? If not: How can one decouple this code in Haskell?
What also puzzles me are the differences in "infinite" types. The above data declaration for "Continuation" is essentially infinite, too. But it works. And I thought I had understood this part...
Any hints greatly appreciated! Thanks in advance, Thomas
PS: The minimal "program" to get it type check is:
data Expression = Null | Num Int | Id String | List [Expression] deriving (Eq, Show)
cdr :: Expression -> Expression cdr (List []) = error "cdr Null !" cdr (List (_:[])) = Null cdr (List (l:ls)) = List ls
car :: Expression -> Expression car (List l) = head l
isNull Null = True isNull _ = False
eval e k = case (car e) of (Id "begin") -> eval_begin (cdr e) k
eval_begin e k = eval (car e) (if isNull (cdr e) then k else (BeginCont k (cdr e)))
-- replace the following 5 lines... data Continuation = BeginCont Continuation Expression
resume k e = case k of BeginCont k' es -> eval_begin es k'
{- ... with these to see the error class Continuation a where resume :: a -> Expression -> Expression
data BeginCont a = BeginCont a Expression deriving (Show) instance (Continuation a) => Continuation (BeginCont a) where resume (BeginCont k es) v = eval_begin es k -]
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (7)
-
Arlen Cuss
-
austin seipp
-
Brandon Allbery
-
Brent Yorgey
-
David Place
-
Thomas
-
Tom Murphy