
I thought I was getting pretty good at Haskell, until I ran into this problem. It's basically a way of maintaining encapsulation of data and functions while being able to have a container, such as a list, hold these items without worrying about their differences. In OO this would be pretty easy. You'd have an interface of some sort and the container would hold objects of the interface type. Then you could write the individual classes that implement that interface in their own files and the main program wouldn't have to know about the details. I'm trying to write a silly little life simulator. We've got a world where many different entities exist. These entities are all different, but for a start we'll use fish and shark. The fish like to swim around in the sea, and will manage to eat some amount of the overall food supply. The amount they consume from year to year varies and they have to consume a minimum amount every year or they die. When they've eaten enough food and have build up a surplus, they'll reproduce, but if they're starving they can't. Sharks are similar, except their food supply is the fish. The two are very similar, but do slightly different things. And every fish or shark has to keep track of its own amount of consumed food. If I wanted to define these separately, the best I've come up with is to create a data type that has all the information necessary, then somewhere maintain a master algebraic data type which wraps each of these in a type constructor. I can then write another head for a general function that will match that type constructor and describe the behavior. I tried something clever with closures, but it turned out to be too clever for me and I couldn't avoid infinite types. Thoughts? Drew Haven drew.haven@gmail.com

I think I found the answers to all my questions at
http://www.haskell.org/haskellwiki/Existential_type
Drew Haven
drew.haven@gmail.com
On Wed, Aug 25, 2010 at 9:43 PM, Drew Haven
I thought I was getting pretty good at Haskell, until I ran into this problem. It's basically a way of maintaining encapsulation of data and functions while being able to have a container, such as a list, hold these items without worrying about their differences. In OO this would be pretty easy. You'd have an interface of some sort and the container would hold objects of the interface type. Then you could write the individual classes that implement that interface in their own files and the main program wouldn't have to know about the details.
I'm trying to write a silly little life simulator. We've got a world where many different entities exist. These entities are all different, but for a start we'll use fish and shark. The fish like to swim around in the sea, and will manage to eat some amount of the overall food supply. The amount they consume from year to year varies and they have to consume a minimum amount every year or they die. When they've eaten enough food and have build up a surplus, they'll reproduce, but if they're starving they can't. Sharks are similar, except their food supply is the fish. The two are very similar, but do slightly different things. And every fish or shark has to keep track of its own amount of consumed food.
If I wanted to define these separately, the best I've come up with is to create a data type that has all the information necessary, then somewhere maintain a master algebraic data type which wraps each of these in a type constructor. I can then write another head for a general function that will match that type constructor and describe the behavior.
I tried something clever with closures, but it turned out to be too clever for me and I couldn't avoid infinite types.
Thoughts?
Drew Haven drew.haven@gmail.com

Hi Drew
Bear in mind though that existentials are not equivalent to subtyping in OO.
For instance, with example 2.1 from [1] all you can do with an Obj is
show it, so for the list xs all you can do is show the elements:
data Obj = forall a. (Show a) => Obj a
xs :: [Obj]
xs = [Obj 1, Obj "foo", Obj 'c']
Because Obj is an existential you can't do an case analysis on it - so
you can't write a function like this:
add_one_if_int (Obj (n::Int)) = Obj (n+1)
add_one_if_int (Obj other) = Obj other
There really is nothing you can do with Obj other than show it.
If you are trying to transliterate OO designs, you might quickly find
existentials are too inert to be useful.
Best wishes
Stephen
[1] http://www.haskell.org/haskellwiki/Existential_type
On 26 August 2010 07:45, Drew Haven
I think I found the answers to all my questions at http://www.haskell.org/haskellwiki/Existential_type

From what I understand (not much), It seems that type-classes are more-or-less equivalent to OO interfaces (I think OP mentioned this), and that containers with existential types are less more-or-less equivalent to OO containers whose elements implement an interface, the biggest exception being that you can't use anything that isn't a part of the class on the contained values.
As I understand, something like this could be relevant:
class AquaticLifeform a where nutrition :: Int reproduce :: Maybe (a, a)
On Thu, Aug 26, 2010 at 10:08 AM, Stephen Tetley
Hi Drew
Bear in mind though that existentials are not equivalent to subtyping in OO.
For instance, with example 2.1 from [1] all you can do with an Obj is show it, so for the list xs all you can do is show the elements:
data Obj = forall a. (Show a) => Obj a
xs :: [Obj] xs = [Obj 1, Obj "foo", Obj 'c']
Because Obj is an existential you can't do an case analysis on it - so you can't write a function like this:
add_one_if_int (Obj (n::Int)) = Obj (n+1) add_one_if_int (Obj other) = Obj other
There really is nothing you can do with Obj other than show it.
If you are trying to transliterate OO designs, you might quickly find existentials are too inert to be useful.
Best wishes
Stephen
[1] http://www.haskell.org/haskellwiki/Existential_type
On 26 August 2010 07:45, Drew Haven
wrote: I think I found the answers to all my questions at http://www.haskell.org/haskellwiki/Existential_type
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Alex R

On 26 August 2010 08:08, Stephen Tetley
Hi Drew
Bear in mind though that existentials are not equivalent to subtyping in OO.
For instance, with example 2.1 from [1] all you can do with an Obj is show it, so for the list xs all you can do is show the elements:
data Obj = forall a. (Show a) => Obj a
xs :: [Obj] xs = [Obj 1, Obj "foo", Obj 'c']
Because Obj is an existential you can't do an case analysis on it - so you can't write a function like this:
add_one_if_int (Obj (n::Int)) = Obj (n+1) add_one_if_int (Obj other) = Obj other
There really is nothing you can do with Obj other than show it.
But that's because you use Show while defining the Obj data type. You can implement other functionalities, by introducing a custom type class, and implementing functionalities in instance declarations. class Show a => CustomTC a where add_one_if_int :: a -> a instance CustomTC Int where add_one_if_int x = x + 1 instance CustomTC Char where add_one_if_int = id instance CustomTC String where add_one_if_int = id xs :: [Obj] xs = [Obj (1 :: Int), Obj "foo", Obj 'c'] xs' :: [Obj] xs' = map (\ (Obj i) -> Obj (add_one_if_int i) ) xs -- xs' = [Obj 2,Obj "foo",Obj 'c'] If you are trying to transliterate OO designs, you might quickly find
existentials are too inert to be useful.
Best wishes
Stephen
[1] http://www.haskell.org/haskellwiki/Existential_type
On 26 August 2010 07:45, Drew Haven
wrote: I think I found the answers to all my questions at http://www.haskell.org/haskellwiki/Existential_type
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Ozgur Akgun

On 26 August 2010 11:51, Ozgur Akgun
But that's because you use Show while defining the Obj data type. You can implement other functionalities, by introducing a custom type class, and implementing functionalities in instance declarations.
Hi Ozgur This is well known, of course, Ralf Lammel (umlauts on the a in Lammel) and Klaus Ostermann have a catalogue of "shoehorns" to fit OO design into Haskell: http://homepages.cwi.nl/~ralf/gpce06/paper.pdf However these styles aren't exemplary [*] - little Haskell code that I've seen in the wild makes use of them. For instance, having a type class for each operation as per CustomTC seems exorbitant, likewise adding type class contexts to datatype definitions quickly becomes unwieldy: data Obj = forall a. (Show a, AquaticLifeform a, ...) => Obj a Best wishes Stephen [*] Caveat - Figure 16 is quite reminiscent of the "finally tagless" style which is now widely used.

Stephen,
I see your point, and I am not a fan of OO style programming in Haskell. I
just wanted to answer OP's question.
In OOP you can have a list of objects of different types, provided they are
subclasses of a common class. But then. you can only apply methods of the
base class to the elements of this list. (Yes you can do some fiddling to
recover the actual type of an element, but you can do similar things in
Haskell as well)
If you desperately want to achieve this effect in Haskell, you can. But
there most probably are better ways of doing things idiomatically.
Best,
Ozgur
On 26 August 2010 13:16, Stephen Tetley
On 26 August 2010 11:51, Ozgur Akgun
wrote: [SNIP] But that's because you use Show while defining the Obj data type. You can implement other functionalities, by introducing a custom type class, and implementing functionalities in instance declarations.
Hi Ozgur
This is well known, of course, Ralf Lammel (umlauts on the a in Lammel) and Klaus Ostermann have a catalogue of "shoehorns" to fit OO design into Haskell:
http://homepages.cwi.nl/~ralf/gpce06/paper.pdfhttp://homepages.cwi.nl/%7Eralf/gpce06/paper.pdf
However these styles aren't exemplary [*] - little Haskell code that I've seen in the wild makes use of them. For instance, having a type class for each operation as per CustomTC seems exorbitant, likewise adding type class contexts to datatype definitions quickly becomes unwieldy:
data Obj = forall a. (Show a, AquaticLifeform a, ...) => Obj a
Best wishes
Stephen
[*] Caveat - Figure 16 is quite reminiscent of the "finally tagless" style which is now widely used. _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Stephen, I agree with your first point: existentials are not equivalent to subtyping in OO. I disagree with your assertion that existentials are too inert to be useful. In fact, with Data.Typeable you can simulate full-blown dynamic typing quite effectively. Here's a simple example: {-# LANGUAGE ExistentialQuantification, DeriveDataTypeable #-} import Data.Typeable data Obj = forall a . Typeable a => Obj a deriving Typeable getValue :: Typeable a => Obj -> Maybe a getValue (Obj o) = cast o intObj :: Obj intObj = Obj (100 :: Integer) strObj :: Obj strObj = Obj "foobar" floatObj :: Obj floatObj = Obj (3.1415 :: Float) test :: Obj -> IO () test o = case getValue o of (Just i :: Maybe Integer) -> print i _ -> print "not an integer" isInt :: Obj -> Bool isInt o = case getValue o of (Just _ :: Maybe Integer) -> True _ -> False isFloat :: Obj -> Bool isFloat o = case getValue o of (Just _ :: Maybe Float) -> True _ -> False isStr :: Obj -> Bool isStr o = case getValue o of (Just _ :: Maybe String) -> True _ -> False test2 :: Obj -> IO () test2 o = if isInt o then print "int" else if isFloat o then print "float" else if isStr o then print "string" else print "unknown" Trying this code out, we have: ghci> test intObj 100 ghci> test strObj "not an integer" ghci> test floatObj "not an integer" ghci> test2 intObj "int" ghci> test2 strObj "string" ghci> test2 floatObj "float" Existentials with type classes are equivalent to interfaces in most OO languages. Existentials with Typeable give you dynamic typing. The Data.Dynamic library provides the dynamic typing functions for you. There are some limitations to this approach with respect to polymorphism, but the same (or worse) limits would be seen in most OO languages. Mike On 8/26/10 12:08 AM, Stephen Tetley wrote:
Hi Drew
Bear in mind though that existentials are not equivalent to subtyping in OO.
For instance, with example 2.1 from [1] all you can do with an Obj is show it, so for the list xs all you can do is show the elements:
data Obj = forall a. (Show a) => Obj a
xs :: [Obj] xs = [Obj 1, Obj "foo", Obj 'c']
Because Obj is an existential you can't do an case analysis on it - so you can't write a function like this:
add_one_if_int (Obj (n::Int)) = Obj (n+1) add_one_if_int (Obj other) = Obj other
There really is nothing you can do with Obj other than show it.
If you are trying to transliterate OO designs, you might quickly find existentials are too inert to be useful.
Best wishes
Stephen
[1] http://www.haskell.org/haskellwiki/Existential_type
On 26 August 2010 07:45, Drew Haven
wrote: I think I found the answers to all my questions at http://www.haskell.org/haskellwiki/Existential_type
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hello Michael I think I put my point forward with too little nuance, my point wasn't that existentials aren't useful[*] (I did call them inert rather then useless...), but that they aren't the rosetta stone for getting to flexible designs. They do solve the original posters problem of putting objects different types in a list, but with the expense that they need heavy use of classes afterwards to be able to manipulate them. For the original problem, dynamic typing with Data.Typeable would probably be a better solution as it avoids annotating the existential Obj type with every class the simulation needs. Best wishes Stephen [*] I think with just existentials you can get dynamic types - Data.Typeable itself use a couple of other tricks (unsafe coerce), see "Typing Dynamic Typing" Arthur I. Baars and S. Doaitse Swierstra or "A Lightweight Implementation of Generics and Dynamics" James Cheney and Ralf Hinze.
participants (5)
-
Alex Rozenshteyn
-
Drew Haven
-
Michael Vanier
-
Ozgur Akgun
-
Stephen Tetley