
You can't. The type can't be known, unfortunately.
With a wrapper like that you typically turn on rank-2 polymorphism and apply
a function to the value directly:
withBar :: Bar -> (forall a. BarLike a => a -> r) ->r
withBar (Bar x) = f x
Hope this helps,
Dan
On Sat, Dec 26, 2009 at 9:58 AM, haskell@kudling.de
Hi,
while this works:
data Foo a = Foo a
unwrapFoo :: Foo a -> a unwrapFoo (Foo x) = x
this:
{-# LANGUAGE ExistentialQuantification #-}
class BarLike a where doSomething :: a -> Double
data Bar = forall a. BarLike a => Bar a
unwrapBar :: Bar -> a unwrapBar (Bar x) = x
gives me:
Couldn't match expected type `a' against inferred type `a1' `a' is a rigid type variable bound by the type signature for `unwrapBar' at test.hs:8:20 `a1' is a rigid type variable bound by the constructor `Bar' at test.hs:9:11 In the expression: x In the definition of `unwrapBar': unwrapBar (Bar x) = x
How can i deconstruct the enclosed value of type a?
Thanks, Lenny
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe