
Hi, just a silly question (or maybe more than one): In Haskell we have data types (Integer,[a],...) as well as type classes (Num, Ord...). But, if we have type classes do we still need types? Why shouldn't the objects that we process be defined only by their 'interfaces' (assuming that a type class is a kind of interface)? Maybe the real question is: are type classes a more primitive concept than data types? And if so, in a language that had only type classes what would a data declaration like the following map to: data List a = Cons a (List a) | Nil And what about pattern matching? Would that still be possible, and what form would it take? And finally, would having only type classes make the type system any simpler? Thanks, titto

Together with Sebastiaan Visser, I've been working on a library called AwesomePrelude [1]. This is a library where we try to reimplement the Prelude by replacing all concrete data types with type classes. This way you can have multiple implementations of a "data type". This is our current implementation of a list:
class ListC j where nil :: j [a] cons :: j a -> j [a] -> j [a] list :: j r -> (j a -> j [a] -> j r) -> j [a] -> j r
The two constructors (Nil, Cons) have been replaced by two equivalent methods (nil, cons), and the concept of pattern matching for this data type has been replaced by a single method (list). A couple of weeks ago, we presented [2] the current version of the library. Where we have JavaScript instances for the different type classes. E.g:
xs ++ ys
Represents a JavaScript AST that concatenates two JavaScript lists.
And finally, would having only type classes make the type system any simpler?
In our library, the types definitely don't get simpler, but thats
probably because it also still deals with concrete JavaScript data
types.
- Tom Lokhorst
[1]: http://github.com/tomlokhorst/AwesomePrelude
[2]: http://tom.lokhorst.eu/2010/02/awesomeprelude-presentation-video
On Fri, Feb 26, 2010 at 1:35 PM, Pasqualino "Titto" Assini
Hi, just a silly question (or maybe more than one):
In Haskell we have data types (Integer,[a],...) as well as type classes (Num, Ord...).
But, if we have type classes do we still need types?
Why shouldn't the objects that we process be defined only by their 'interfaces' (assuming that a type class is a kind of interface)?
Maybe the real question is: are type classes a more primitive concept than data types?
And if so, in a language that had only type classes what would a data declaration like the following map to:
data List a = Cons a (List a) | Nil
And what about pattern matching? Would that still be possible, and what form would it take?
And finally, would having only type classes make the type system any simpler?
Thanks,
titto _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

A type is, well, a type. A type class is a relation between types. The confusion probably comes from OO programming where (interfaces) describe unary relations (= one parameter type classes). (begin rant) I wouldn't easily give up algebraic data types just because OO programmers don't seem know about them - so the re-invent them and call it "composite" pattern...

A type class is a relation between types.
Yes, but not officially, just de facto: http://hackage.haskell.org/trac/haskell-prime/ticket/90 Best, Maurício

I'd say we don't really need subclasses. I mean, what's the difference: class Eq a where (==) :: a -> a -> Bool instance Eq a => Eq (Maybe a) where Nothing == Nothing = True Just x == Just y = x == y _ == _ = False sort :: Eq a => [a] -> [a] or data Eq a = Eq {eq :: a -> a -> Bool} eqMaybe :: Eq a -> Eq (Maybe a) eqMaybe e = Eq {eq = eqM} where eqM Nothing Nothing = True eqM (Just x) (Just y) = eq e x y eqM _ _ = False sort :: Eq a -> [a] -> [a] Replacing classes with types, we only lose one thing: the compiler won't deduce the right instances for us. I'll trade it for the ability to abstract over them. After all, we CAN deduce the right instances by hand, it's just a finite amount of work (not very big, in my experience). Pasqualino "Titto" Assini wrote:
Hi, just a silly question (or maybe more than one):
In Haskell we have data types (Integer,[a],...) as well as type classes (Num, Ord...).
But, if we have type classes do we still need types?
Why shouldn't the objects that we process be defined only by their 'interfaces' (assuming that a type class is a kind of interface)?
Maybe the real question is: are type classes a more primitive concept than data types?
And if so, in a language that had only type classes what would a data declaration like the following map to:
data List a = Cons a (List a) | Nil
And what about pattern matching? Would that still be possible, and what form would it take?
And finally, would having only type classes make the type system any simpler?
Thanks,
titto _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

s/subclasses/classes/ Sorry for the confusion. Miguel Mitrofanov wrote:
I'd say we don't really need subclasses. I mean, what's the difference:
class Eq a where (==) :: a -> a -> Bool instance Eq a => Eq (Maybe a) where Nothing == Nothing = True Just x == Just y = x == y _ == _ = False sort :: Eq a => [a] -> [a]
or
data Eq a = Eq {eq :: a -> a -> Bool} eqMaybe :: Eq a -> Eq (Maybe a) eqMaybe e = Eq {eq = eqM} where eqM Nothing Nothing = True eqM (Just x) (Just y) = eq e x y eqM _ _ = False sort :: Eq a -> [a] -> [a]
Replacing classes with types, we only lose one thing: the compiler won't deduce the right instances for us. I'll trade it for the ability to abstract over them. After all, we CAN deduce the right instances by hand, it's just a finite amount of work (not very big, in my experience).
Pasqualino "Titto" Assini wrote:
Hi, just a silly question (or maybe more than one):
In Haskell we have data types (Integer,[a],...) as well as type classes (Num, Ord...).
But, if we have type classes do we still need types?
Why shouldn't the objects that we process be defined only by their 'interfaces' (assuming that a type class is a kind of interface)?
Maybe the real question is: are type classes a more primitive concept than data types?
And if so, in a language that had only type classes what would a data declaration like the following map to:
data List a = Cons a (List a) | Nil
And what about pattern matching? Would that still be possible, and what form would it take?
And finally, would having only type classes make the type system any simpler?
Thanks,
titto _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

This reminds me of an email posted to this list long ago
by Luke Palmer, describing a use of records-as-interfaces
in Agda.
--
Jason Dusek
---------- Forwarded message ----------
From: Luke Palmer
Consider the real numbers. They "are" a group. We have an identity element `0', inverses and closure under the associative operation `+'.
Group+ = (+, 0, -1 * _)
They are another group, too -- the group with `*':
Group* = (*, 1, 1 / _)
Ignoring 0 for sake of discussion.
This seems like a real problem with the whole notion of typeclasses -- we can't really say a set/type "is" its extension with some new operations.
One road to go on this is to make every extension of the set with new ops a different type; but that seems really horribly inconvenient. I wonder what approaches have been tried here?
I consider typeclasses a happy notational medium. They are not perfect, they miss some cases, but they are pretty good. For full generality at the expense of some verbosity, I like Agda's solution pretty well. Agda allows you to "open" a record into a scope. record Group (a : Set) where field _+_ : a -> a -> a -_ : a -> a 0 : a conj : {a : Set} -> Group a -> a -> a -> a conj g x y = x + y + (-x) where open g Maybe I even got the syntax right :-P The cool thing is that you can use this for the invariant-keeping property of typeclasses, too. Eg. Data.Map relies on the fact that there is at most one Ord instance per type. By parameterizing the module over the Ord record, we can do the same: record Ord (a : Set) where ... module MapMod (a : Set) (ord : Ord a) where Map : b -> Set Map = ... insert : {b : Set} -> a -> b -> Map b -> Map b insert = ... ... So we have the liberty of being able to use different Ord instances, but different Ord instances give rise to different Map types, so we can not violate any invariants. You can do something similar in Haskell using an existential type, although it is very inconvenient: data Ord a = ... data MapMod map a b = MapMod { empty :: map a b, insert :: a -> b -> map a b -> map a b, ... } withMap :: Ord a -> (forall map. MapMod map a b -> z) -> z withMap ord f = f ( {- implement MapMod here, using ord for ordering }- ) Then you could use maps on different Ords for the same type, but they could not talk to each other. Some syntax sugar could help the Haskell situation quite a lot.

On Fri, Feb 26, 2010 at 04:23:52PM +0300, Miguel Mitrofanov wrote:
I'd say we don't really need subclasses. I mean, what's the difference:
class Eq a where (==) :: a -> a -> Bool instance Eq a => Eq (Maybe a) where Nothing == Nothing = True Just x == Just y = x == y _ == _ = False sort :: Eq a => [a] -> [a]
or
data Eq a = Eq {eq :: a -> a -> Bool} eqMaybe :: Eq a -> Eq (Maybe a) eqMaybe e = Eq {eq = eqM} where eqM Nothing Nothing = True eqM (Just x) (Just y) = eq e x y eqM _ _ = False sort :: Eq a -> [a] -> [a]
Replacing classes with types, we only lose one thing: the compiler won't deduce the right instances for us. I'll trade it for the ability to abstract over them. After all, we CAN deduce the right instances by hand, it's just a finite amount of work (not very big, in my experience).
But then we would lose the invarient that there is a unique pairing between a type and a given class. for instance, you would no longer be able to implement things like Set and Map, For instance if you called the two following functions with different ord arguments, you would suddenly break all the invarients of what 'Set' means. insert :: Ord a -> a -> Set a -> Set a member :: Ord a -> a -> Set a -> Bool The unique correspondence between types and classes (i.e. no local instances) is a main _feature_ of type classes. Often when people think they need local instances, they are just applying type classes when they should be using a different idiom, such as the one you mention. John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
participants (8)
-
Daniel Fischer
-
Jason Dusek
-
Johannes Waldmann
-
John Meacham
-
Maurício CA
-
Miguel Mitrofanov
-
Pasqualino "Titto" Assini
-
Tom Lokhorst