[Haskell-cafe] How to understand the 'forall' ?

Sean Leather leather at cs.uu.nl
Wed Sep 2 09:30:14 EDT 2009


> I think I've understood the existential types thing, but I still can't
> put them to work when I think to a solution for a particular problem,
> i.e. it's not among my programming tools yet.
>

Here's another commonly found, easy-to-understand example that's useful.

> {-# LANGUAGE ExistentialQuantification #-}
>
> module Main where
>
> data Showable = forall a . Show a => S a
>
> instance Show Showable where
>   show (S x) = show x
>
> main = print [S 1, S 'a', S 9.4, S (Just 2)] -- prints [1,'a',9.4,Just 2]

The datatype says that for any type 'a' with an instance of 'Show a', we can
construct a value of 'Showable'. While we normally wouldn't be able to build
a list with different types, we can now create a [Showable] list with
existential types.

Sean
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090902/82a6cc41/attachment-0001.html


More information about the Haskell-Cafe mailing list