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

Per Vognsen per.vognsen at gmail.com
Wed Sep 2 10:04:12 EDT 2009


You can of course achieve the same thing by reifying the Show
dictionary as a record and having Showable's Show instance forward to
the dictionary.

A really good paper for an overview of the strengths and weaknesses of
different object encodings (recursive records vs existentials vs
recursive existentials vs bounded existentials) for cases more
complicated than the one below is Comparing Object Encodings by Bruce,
Cardelli and Pierce. Much of the same discussion is also replicated in
Pierce's Types and Programming Languages in a less technical, more
readable form.

-Per


On Wed, Sep 2, 2009 at 10:30 PM, Sean Leather<leather at cs.uu.nl> wrote:
>
>> 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
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


More information about the Haskell-Cafe mailing list