summaryrefslogtreecommitdiffstats
path: root/lib/Phi/Widgets/AlphaBox.hs
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Phi/Widgets/AlphaBox.hs')
-rw-r--r--lib/Phi/Widgets/AlphaBox.hs39
1 files changed, 18 insertions, 21 deletions
diff --git a/lib/Phi/Widgets/AlphaBox.hs b/lib/Phi/Widgets/AlphaBox.hs
index 2db17f4..eacda5a 100644
--- a/lib/Phi/Widgets/AlphaBox.hs
+++ b/lib/Phi/Widgets/AlphaBox.hs
@@ -1,6 +1,7 @@
-{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE MultiParamTypeClasses, StandaloneDeriving, ExistentialQuantification, FlexibleInstances #-}
-module Phi.Widgets.AlphaBox ( alphaBox
+module Phi.Widgets.AlphaBox ( AlphaBox
+ , alphaBox
) where
import Phi.Types
@@ -11,25 +12,23 @@ import Control.Monad
import Graphics.Rendering.Cairo
-data AlphaBoxState = AlphaBoxState ![WidgetState] deriving Eq
+data AlphaBox w d = (Widget w d) => AlphaBox !Double !w
+deriving instance Show (AlphaBox w d)
+deriving instance Eq (AlphaBox w d)
-data AlphaBox = AlphaBox !Double ![Widget] deriving (Show, Eq)
-
-
-instance WidgetClass AlphaBox AlphaBoxState where
- initWidget (AlphaBox _ widgets) phi disp = liftM AlphaBoxState $ mapM (createWidgetState phi disp) widgets
+instance Eq d => Widget (AlphaBox w d) d where
+ initWidget (AlphaBox _ w) = initWidget w
- minSize (AlphaBox _ _) (AlphaBoxState widgetStates) height screen =
- sum (map (\(WidgetState {stateWidget = w, statePrivateData = priv}) -> minSize w priv height screen) widgetStates)
+ minSize (AlphaBox _ w) = minSize w
- weight (AlphaBox _ widgets) = sum (map (\(Widget w) -> weight w) widgets)
+ weight (AlphaBox _ w) = weight w
- layout (AlphaBox _ _) (AlphaBoxState widgetStates) width height screen = AlphaBoxState $ layoutWidgets widgetStates 0 0 width height screen
+ layout (AlphaBox _ w) = layout w
- render (AlphaBox alpha _) (AlphaBoxState widgetStates) x y w h screen = do
- renderWithSimilarSurface ContentColorAlpha w h $ \surface -> do
+ render (AlphaBox alpha w) d x y width height screen = do
+ renderWithSimilarSurface ContentColorAlpha width height $ \surface -> do
renderWith surface $ do
- renderWidgets widgetStates screen x y
+ render w d x y width height screen
setOperator OperatorDestIn
setSourceRGBA 0 0 0 alpha
@@ -37,12 +36,10 @@ instance WidgetClass AlphaBox AlphaBoxState where
withPatternForSurface surface setSource
paint
-
-
-
- handleMessage _ (AlphaBoxState widgetStates) m = AlphaBoxState $ handleMessageWidgets m widgetStates
+
+ handleMessage (AlphaBox _ w) = handleMessage w
-alphaBox :: Double -> [Widget] -> Widget
-alphaBox alpha = Widget . AlphaBox alpha
+alphaBox :: (Widget w d) => Double -> w -> AlphaBox w d
+alphaBox = AlphaBox