
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

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

On 26 Dec 2009, at 11:58, haskell@kudling.de wrote:
class BarLike a where doSomething :: a -> Double
data Bar = forall a. BarLike a => Bar a
unwrapBar :: Bar -> a unwrapBar (Bar x) = x
How can i deconstruct the enclosed value of type a?
You can't write a function with a type that mentions existentially quantified "a". Period. But you can deconstruct the enclosed value temporarily: getSomething :: Bar -> Double getSomething b = case b of Bar a -> doSomething a

Hi all, thanks for the insight.
But you can deconstruct the enclosed value temporarily:
getSomething :: Bar -> Double getSomething b = case b of Bar a -> doSomething a
Somehow i fail to apply this. If you look at http://chlor.svn.sourceforge.net/viewvc/chlor/trunk/haskell/Chlor/Object.hs?revision=603&view=markup in line 26 i used this for function "adjustToBox", but i still get: Chlor/Object.hs:33:36: Couldn't match expected type `ObjectWrapper' against inferred type `a' `a' is a rigid type variable bound by the constructor `ObjectWrapper' at Chlor/Object.hs:33:12 In the expression: adjustToBox object In a case alternative: ObjectWrapper object -> adjustToBox object In the expression: case wrapper of { ObjectWrapper object -> adjustToBox object } :(

Your code is equivalent to this: adjustToBox (ObjectWrapper object) box = adjustToBox object box but what you've probably intended to write was adjustToBox (ObjectWrapper object) box = ObjectWrapper (adjustToBox object box) It has nothing to do with existentials - it's a simple type mismatch. On 26 Dec 2009, at 19:53, haskell@kudling.de wrote:
Hi all,
thanks for the insight.
But you can deconstruct the enclosed value temporarily:
getSomething :: Bar -> Double getSomething b = case b of Bar a -> doSomething a
Somehow i fail to apply this.
If you look at http://chlor.svn.sourceforge.net/viewvc/chlor/trunk/haskell/Chlor/Object.hs?revision=603&view=markup
in line 26 i used this for function "adjustToBox", but i still get:
Chlor/Object.hs:33:36: Couldn't match expected type `ObjectWrapper' against inferred type `a' `a' is a rigid type variable bound by the constructor `ObjectWrapper' at Chlor/Object.hs:33:12 In the expression: adjustToBox object In a case alternative: ObjectWrapper object -> adjustToBox object In the expression: case wrapper of { ObjectWrapper object -> adjustToBox object }
:( _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Oh, you're right, thanks.
I got lost in types and GHC error messages. :/
Miguel Mitrofanov
Your code is equivalent to this:
adjustToBox (ObjectWrapper object) box = adjustToBox object box
but what you've probably intended to write was
adjustToBox (ObjectWrapper object) box = ObjectWrapper (adjustToBox object box)
It has nothing to do with existentials - it's a simple type mismatch.
On 26 Dec 2009, at 19:53, haskell@kudling.de wrote:
Hi all,
thanks for the insight.
But you can deconstruct the enclosed value temporarily:
getSomething :: Bar -> Double getSomething b = case b of Bar a -> doSomething a
Somehow i fail to apply this.
If you look at http://chlor.svn.sourceforge.net/viewvc/chlor/trunk/haskell/Chlor/Object.hs?revision=603&view=markup
in line 26 i used this for function "adjustToBox", but i still get:
Chlor/Object.hs:33:36: Couldn't match expected type `ObjectWrapper' against inferred type `a' `a' is a rigid type variable bound by the constructor `ObjectWrapper' at Chlor/Object.hs:33:12 In the expression: adjustToBox object In a case alternative: ObjectWrapper object -> adjustToBox object In the expression: case wrapper of { ObjectWrapper object -> adjustToBox object }
:( _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Daniel Peebles
-
haskell@kudling.de
-
Miguel Mitrofanov