summaryrefslogtreecommitdiffstats
path: root/lib/Phi/Widgets
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Phi/Widgets')
-rw-r--r--lib/Phi/Widgets/AlphaBox.hs39
-rw-r--r--lib/Phi/Widgets/Clock.hs6
-rw-r--r--lib/Phi/Widgets/Systray.hs18
-rw-r--r--lib/Phi/Widgets/Taskbar.hs8
4 files changed, 29 insertions, 42 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
diff --git a/lib/Phi/Widgets/Clock.hs b/lib/Phi/Widgets/Clock.hs
index 2607288..bee8d39 100644
--- a/lib/Phi/Widgets/Clock.hs
+++ b/lib/Phi/Widgets/Clock.hs
@@ -43,7 +43,7 @@ data ClockState = ClockState !ZonedTime deriving (Show, Eq)
data ClockMessage = UpdateTime !ZonedTime deriving (Show, Typeable)
-instance WidgetClass Clock ClockState where
+instance Widget Clock ClockState where
initWidget (Clock _) phi _ = do
forkIO $ forever $ do
time <- getZonedTime
@@ -85,6 +85,6 @@ instance WidgetClass Clock ClockState where
_ -> priv
-clock :: ClockConfig -> Widget
+clock :: ClockConfig -> Clock
clock config = do
- Widget $ Clock config \ No newline at end of file
+ Clock config \ No newline at end of file
diff --git a/lib/Phi/Widgets/Systray.hs b/lib/Phi/Widgets/Systray.hs
index e9311de..6812018 100644
--- a/lib/Phi/Widgets/Systray.hs
+++ b/lib/Phi/Widgets/Systray.hs
@@ -35,19 +35,9 @@ import Phi.Widget
import Phi.X11.Atoms
-instance Show Display where
- show _ = "Display <?>"
-
-instance Show Phi where
- show _ = "Phi <?>"
-
-instance Show (IORef a) where
- show _ = "IORef <?>"
-
-
data SystrayIconState = SystrayIconState !Window !Window deriving Show
-data SystrayState = SystrayState !Phi !Rectangle !Int !(IORef Int) ![SystrayIconState] deriving Show
+data SystrayState = SystrayState !Phi !Rectangle !Int !(IORef Int) ![SystrayIconState]
instance Eq SystrayState where
_ == _ = False
@@ -57,7 +47,7 @@ data SystrayMessage = AddIcon !Window !Window | RemoveIcon !Window | RenderIcon
deriving (Show, Typeable)
-instance WidgetClass Systray SystrayState where
+instance Widget Systray SystrayState where
initWidget (Systray) phi dispvar = do
phi' <- dupPhi phi
forkIO $ systrayRunner phi' dispvar
@@ -298,5 +288,5 @@ removeIcon phi disp reparent window = do
return ()
-systray :: Widget
-systray = Widget $ Systray
+systray :: Systray
+systray = Systray
diff --git a/lib/Phi/Widgets/Taskbar.hs b/lib/Phi/Widgets/Taskbar.hs
index feb7246..c17ac36 100644
--- a/lib/Phi/Widgets/Taskbar.hs
+++ b/lib/Phi/Widgets/Taskbar.hs
@@ -7,6 +7,7 @@ module Phi.Widgets.Taskbar ( IconStyle
, DesktopStyle(..)
, TaskbarConfig(..)
, defaultTaskbarConfig
+ , Taskbar
, taskbar
) where
@@ -165,7 +166,7 @@ data TaskbarMessage = WindowListUpdate ![Xlib.Window] !(M.Map Window WindowState
instance Show (IORef a) where
show _ = "IORef <?>"
-instance WidgetClass Taskbar TaskbarState where
+instance Widget Taskbar TaskbarState where
initWidget (Taskbar _) phi dispvar = do
phi' <- dupPhi phi
forkIO $ taskbarRunner phi' dispvar
@@ -566,6 +567,5 @@ showWindow disp atoms window = do
getWindowList :: Xlib.Display -> Atoms -> IO [Window]
getWindowList disp atoms = liftM (map fromIntegral . join . maybeToList) $ XExtras.getWindowProperty32 disp (atom_NET_CLIENT_LIST atoms) $ Xlib.defaultRootWindow disp
-taskbar :: TaskbarConfig -> Widget
-taskbar config = do
- Widget $ Taskbar config
+taskbar :: TaskbarConfig -> Taskbar
+taskbar = Taskbar