On 9/8/07, Ryan Ingram <[EMAIL PROTECTED]> wrote:
> This does what you want, I think:
>
> {-# LANGUAGE ExistentialQuantification #-}
> module Exist where
>
> data Showable = forall a. (Show a) => Showable a
> instance Show Showable where
>    showsPrec p (Showable a) = showsPrec p a
>    show (Showable a) = show a
>    -- You have to use the default implementation of showList
>    -- because a list could be heterogeneous
>
> data T a = forall b. (Show b) => T b a
>
> extShow :: T a -> Showable
> extShow (T b _) = Showable b

Wow, I'm impressed! Making the existential wrapper an instance of its
own typeclass solves quite a few problems.

While the idiom is obvious in hindsight, I don't think I've seen it
documented before. (Looking around just now I found some oblique
references to the technique, but nothing that really called attention
to itself.)


Stuart
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to