
On Thu, 10 July 2008, Marco TĂșlio Gontijo e Silva wrote:
how do I unbox a existential quantificated data type?
Dan Doel wrote:
elim :: L a -> (forall l. l a -> r) -> r elim (L e) f = f e
Just one catch: You can't actually write a function 'f' of type (forall l. l a -> r) without knowing something about the forgotten type of l. One way to deal with this is by restricting the type of l in the data declaration. For example, you could restrict it to the typeclass Foldable, and then you have access to the methods of that typeclass. \begin{code} {-# LANGUAGE ExistentialQuantification #-} module Main where import qualified Data.Foldable as F data L a = forall l. (F.Foldable l) => L (l a) toList :: L a -> [a] toList (L x) = F.foldr (:) [] x main :: IO () main = do let x = L [1..10] print $ toList x \end{code} See also http://www.haskell.org/haskellwiki/Existential_type