[Haskell-beginners] User-defined polymorphic data type: heterogeneous list?

Arlen Cuss celtic at sairyx.org
Mon Jul 11 08:21:44 CEST 2011


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



More information about the Beginners mailing list