[Haskell-cafe] Problem on existential type.

Magicloud Magiclouds magicloud.magiclouds at gmail.com
Fri Sep 4 02:05:23 EDT 2009


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

-- 
竹密岂妨流水过
山高哪阻野云飞


More information about the Haskell-Cafe mailing list