Problem on existential type.

Hi, I am trying out existential type, some sample code works well. Well, my own code could not be compiled with message: Grid.hs:45:11: Kind error: `GridWidget' is applied to too many type arguments In the type `GridWidget widget' In the type `(GridWidget widget) -> (widget -> t) -> t' In the type signature for `liftGW': liftGW :: (GridWidget widget) -> (widget -> t) -> t The code is: {-# OPTIONS -fglasgow-exts #-} module Grid where import Graphics.UI.Gtk data GridWidgetType = GridLabel | GridTextView data GridWidget = forall widget. (WidgetClass widget) => GridWidget widget --GWLabel Label -- | GWTextView TextView gridNew defaultWidget = do self <- fixedNew -- gw <- gridWidgetNew defaultWidget -- gridAddWidget self gw (0, 0) -- self `on` realize $ do -- (ww, wh) <- liftGW gw widgetGetSize -- (w, h) <- widgetGetSize self -- mapM_ (\x -> -- mapM_ (\y -> do -- gw <- gridWidgetNew defaultWidget -- liftGW gw $ \gw -> fixedPut self gw (x * ww, y * wh) -- ) [0..floor (h / wh)] -- ) [0..floor (w / ww)] return self -- gridSetWidget self (x, y) widget = do -- w <- gridGetWidget self (x, y) -- if w == widget -- then return () -- else do -- (w, h) <- widgetGetSize w -- gw <- gridWidgetNew widget -- fixedPut self gw (x * w, y * h) -- widgetDestroy w -- gridWidgetNew GridLabel = labelNew Nothing >>= return . GW -- gridWidgetNew GridTextView = textViewNew >>= return . GW -- gridAddWidget grid (GWLabel label) (x, y) = fixedPut grid label (x, y) -- gridAddWidget grid (GWTextView textView) (x, y) = fixedPut grid textView (x, y) liftGW :: (GridWidget widget) -> (widget -> t) -> t liftGW (GridWidget label) f = f label liftGW (GridWidget textView) f = f textView -- 竹密岂妨流水过 山高哪阻野云飞

The only knowledge the type system has about a GridWidget is that it contains /some thing/ which is a member of the WidgetClass typeclass. So the only thing you can do with the thing inside the GridWidget is to apply functions of the WidgetClass. It might be easier to see with the Show class instead of your WidgetClass. data GridWidget = forall w. (Show w) => GridWidget w foo :: GridWidget -> String foo (GridWidget w) = show w foo $ GridWidget "hi there"
"hi there" foo $ GridWidget (3, 5) "(3,5)" map foo [GridWidget True, GridWidget 3.14159] ["True", "3.14159"]
But 'show' is the only function you can apply to values inside of a
GridWidget because it is the only function of the Show class. The same
holds for you WidgetClass.
On Fri, Sep 4, 2009 at 8:13 AM, Miguel Mitrofanov
Your data type GridWidget doesn't have a parameter, yet you use it like it has one.
data GridWidget = forall widget. (WidgetClass widget) => GridWidget widget
^ | NB:-------------+
liftGW :: (GridWidget widget) -> (widget -> t) -> t

Miguel Mitrofanov wrote:
Your data type GridWidget doesn't have a parameter, yet you use it like it has one.
data GridWidget = forall widget. (WidgetClass widget) => GridWidget widget ^ | NB:-------------+
This is allowed as long as you have enabled the ExistentialTypes extension. This declares a so-called existential type, see the wiki for details, http://www.haskell.org/haskellwiki/Existential_types . Note that the second occurrence of "GridWidget" defines a data constructor, not a type constructor. Cheers, Jochem -- Jochem Berndsen | jochem@functor.nl GPG: 0xE6FABFAB

On Thu, Sep 3, 2009 at 11:05 PM, Magicloud
Magiclouds
data GridWidget = forall widget. (WidgetClass widget) => GridWidget widget
liftGW :: (GridWidget widget) -> (widget -> t) -> t liftGW (GridWidget label) f = f label liftGW (GridWidget textView) f = f textView
The type signature on liftGW is wrong. Also, as mentioned elsewhere, the two matches overlap; the second case never gets called. The correct type signature for "liftGW" is: liftGW :: GridWidget -> (forall widget. WidgetClass widget => widget -> t) -> t Note that the "f" passed in has to accept *any* widget type, so it's possible that existential types aren't what you want. -- ryan

Thank you all guys. This explained so much.
On Sun, Sep 6, 2009 at 2:53 AM, Ryan Ingram
On Thu, Sep 3, 2009 at 11:05 PM, Magicloud Magiclouds
wrote: data GridWidget = forall widget. (WidgetClass widget) => GridWidget widget
liftGW :: (GridWidget widget) -> (widget -> t) -> t liftGW (GridWidget label) f = f label liftGW (GridWidget textView) f = f textView
The type signature on liftGW is wrong. Also, as mentioned elsewhere, the two matches overlap; the second case never gets called.
The correct type signature for "liftGW" is:
liftGW :: GridWidget -> (forall widget. WidgetClass widget => widget -> t) -> t
Note that the "f" passed in has to accept *any* widget type, so it's possible that existential types aren't what you want.
-- ryan
-- 竹密岂妨流水过 山高哪阻野云飞
participants (5)
-
Jochem Berndsen
-
Magicloud Magiclouds
-
Miguel Mitrofanov
-
Roel van Dijk
-
Ryan Ingram