User-defined polymorphic data type: heterogeneous list?

I'm trying to understand parametric polymorphism and polymorphic data types. I especially want to go beyond simply using the defined polymorphic data types (lists and so forth) and see how I can make my own useful ones. As my first stab at it, it seemed like I should be able to create my own heterogeneous "list" data type -- i.e., a "list" data type that can contain elements of different types. (like, [3,'a',True], for example) But I'm a little stuck. My first try was like so: data HeteroList a b = Null | Element a (HeteroList a b) deriving (Show) ...but this of course did not work, because all elements end up having to be the same type. Then I tried data HeteroList a b = Null | Element a (HeteroList b a) deriving (Show) ...but this doesn't work because every other other element has to be the same type: Element 'a' (Element 1 (Element 'a' (Element 2 Null))) ...I could go on and embarrass myself some more, but since I'm likely widely off-base I'll just ask if somebody can point me in the right direction. -- frigidcode.com theologia.indicium.us

On 21:00 Sun 10 Jul , Christopher Howard wrote:
I'm trying to understand parametric polymorphism and polymorphic data types. I especially want to go beyond simply using the defined polymorphic data types (lists and so forth) and see how I can make my own useful ones.
As my first stab at it, it seemed like I should be able to create my own heterogeneous "list" data type -- i.e., a "list" data type that can contain elements of different types. (like, [3,'a',True], for example)
But I'm a little stuck. My first try was like so:
data HeteroList a b = Null | Element a (HeteroList a b) deriving (Show)
...but this of course did not work, because all elements end up having to be the same type.
Then I tried
data HeteroList a b = Null | Element a (HeteroList b a) deriving (Show)
...but this doesn't work because every other other element has to be the same type:
Element 'a' (Element 1 (Element 'a' (Element 2 Null)))
...I could go on and embarrass myself some more, but since I'm likely widely off-base I'll just ask if somebody can point me in the right direction.
I'm not an expert on the subject, but existential quantification allows it. {-# LANGUAGE ExistentialQuantification #-} data HeteroElement = forall a. Element a list = [Element 1, Element 'a', Element True] http://en.wikibooks.org/wiki/Haskell/Existentially_quantified_types http://haskell.org/haskellwiki/Heterogenous_collections -- Mats Rauhala MasseR

There are two main ways to get lists with different types.
Method one is the most common.
data MyTypes = MyInt Int | MyString String
--Then in your code you deal with it like so:
blah = map myTypeFunc [MyInt 1, MyString "asdf"]
where
myTypeFunc :: MyTypes -> IO ()
myTypeFunc (MyInt i) = putStrLn $ show i
myTypeFunc (MyString s) = putStrLn s
You can even use parametric types to make it more general
data MyTypes a b c = Type1 a | Type2 b | Type3 c
But you are still going to have to deal with each type explicitly
every function that handles them.
The other way is to use type classes:
class MyClass where
somefunction :: Bool -> a
instance MyClass Int where
somefunction True = 1
somefunction False = 0
instance MyClass String where
somefunction True = "true"
somefunction False = "false"
Then you make functions that ultimately make use of only the class's
functions. Since it is the only property on every element of the list
that is guaranteed to be there, it is all you can use.
myList :: MyClass a => [a]
myList = [somefunction True, somefunction False]
There are cases where one is the better option and cases where the
other is best.
Adapting this to your custom lists, you'd make a datatype like:
data HeteroList = Null | Element MyType HeteroList
On Mon, Jul 11, 2011 at 1:00 AM, Christopher Howard
I'm trying to understand parametric polymorphism and polymorphic data types. I especially want to go beyond simply using the defined polymorphic data types (lists and so forth) and see how I can make my own useful ones.
As my first stab at it, it seemed like I should be able to create my own heterogeneous "list" data type -- i.e., a "list" data type that can contain elements of different types. (like, [3,'a',True], for example)
But I'm a little stuck. My first try was like so:
data HeteroList a b = Null | Element a (HeteroList a b) deriving (Show)
...but this of course did not work, because all elements end up having to be the same type.
Then I tried
data HeteroList a b = Null | Element a (HeteroList b a) deriving (Show)
...but this doesn't work because every other other element has to be the same type:
Element 'a' (Element 1 (Element 'a' (Element 2 Null)))
...I could go on and embarrass myself some more, but since I'm likely widely off-base I'll just ask if somebody can point me in the right direction.
-- frigidcode.com theologia.indicium.us
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

David McBride
myList :: MyClass a => [a] myList = [somefunction True, somefunction False]
This is not a heterogenous list. The list elements would still have to have the same type. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

Hi Christopher,
As my first stab at it, it seemed like I should be able to create my own heterogeneous "list" data type -- i.e., a "list" data type that can contain elements of different types. (like, [3,'a',True], for example)
One problem I can see would be dealing with the contents of such a list. Imagine you have a list with many different types in it. Would every type appear in the type of the list? If so, that would have to be a consideration before you even get to the "=" sign in your data type definition. If not, whence do they come?
But I'm a little stuck. My first try was like so: data HeteroList a b = Null | Element a (HeteroList a b) deriving (Show)
Then I tried data HeteroList a b = Null | Element a (HeteroList b a) deriving (Show)
We can see where that there are never any "new" element types introduced, so you're necessarily limited to two, and as for where they can appear, it's made clear in your own definitions:
data HeteroList a b = Null | Element a (HeteroList a b) deriving (Show)
Here 'a' is plugged back into HeteroList's 'a', and thus is always the actual value of Element.
data HeteroList a b = Null | Element a (HeteroList b a) deriving (Show)
And here, 'a' and 'b' simply switch places. As Mats pointed out, an existential quantification will let you define your polymorphic element (and to quote Mats):
{-# LANGUAGE ExistentialQuantification #-}
data HeteroElement = forall a. Element a
list = [Element 1, Element 'a', Element True]
The question is, what can you do with this list? You can't "show" it, because there's no requirement on HeteroElement's "a" type of it having a Show instance (adding 'deriving Show' to the data statement will cause an error, as it cannot be done for all 'a'!). You can't find out their types. Indeed, you can't do anything at all with an Element, simply because there's no restriction placed on their value. They could contain anything at all. I hope this helps. There's more to the story, though, and that's where someone else will hopefully come in: what use would such a type be? Cheers, A

On Mon, Jul 11, 2011 at 8:21 AM, Arlen Cuss
Hi Christopher,
As my first stab at it, it seemed like I should be able to create my own heterogeneous "list" data type -- i.e., a "list" data type that can contain elements of different types. (like, [3,'a',True], for example)
One problem I can see would be dealing with the contents of such a list. Imagine you have a list with many different types in it. Would every type appear in the type of the list? If so, that would have to be a consideration before you even get to the "=" sign in your data type definition. If not, whence do they come?
That approach can be found in the HList library where indeed the heterogeneous list at the data level is echoed by an heterogeneous list at the type level, the basic blocks are :
data HNil = HNil data HCons e l = HCons e l
but with just that you would have no guarantee that the "l" from HCons was HNil or HCons so you add a typeclass :
class HList l instance HList HNil instance (HList l) => HList (HCons e l)
and you don't export the data constructors but smart constructors instead :
hNil :: HNil hNil = HNil
hCons :: (HList l) => e -> l -> HCons e l hCons x xs = HCons x xs
And thus you have an heterogeneous list which you can manipulate usefully, though HList add plenty of stuff to allow cool tricks. -- Jedaï

Arlen Cuss
As Mats pointed out, an existential quantification will let you define your polymorphic element (and to quote Mats):
{-# LANGUAGE ExistentialQuantification #-}
data HeteroElement = forall a. Element a
list = [Element 1, Element 'a', Element True]
The question is, what can you do with this list? You can't "show" it, because there's no requirement on HeteroElement's "a" type of it having a Show instance (adding 'deriving Show' to the data statement will cause an error, as it cannot be done for all 'a'!). You can't find out their types. Indeed, you can't do anything at all with an Element, simply because there's no restriction placed on their value. They could contain anything at all.
This definition is indeed not very useful, but you can have something like the following: class Renderable a class Updatable a data GameObj = forall a. (Renderable a, Updatable a) => GameObj a list :: [GameObj] list = [ GameObj SpaceMarine, GameObj Zombie, GameObj BFG9000 ] Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
participants (6)
-
Arlen Cuss
-
Chaddaï Fouché
-
Christopher Howard
-
David McBride
-
Ertugrul Soeylemez
-
Mats Rauhala