summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorMatthias Schiffer <mschiffer@universe-factory.net>2011-08-12 03:18:46 +0200
committerMatthias Schiffer <mschiffer@universe-factory.net>2011-08-12 03:18:46 +0200
commit15bccc001a5ff2e76d0890f85e300e9312cddd1b (patch)
tree2e880537f1a1eedebe021ffbd3cb521c2a8c3a28
parent180285af85c4c6c02c885dd6c276a33e0bf00d1a (diff)
downloadphi-15bccc001a5ff2e76d0890f85e300e9312cddd1b.tar
phi-15bccc001a5ff2e76d0890f85e300e9312cddd1b.zip
Some strictness optimizations
-rw-r--r--lib/Phi/Border.hs4
-rw-r--r--lib/Phi/Panel.hs4
-rw-r--r--lib/Phi/Phi.hs2
-rw-r--r--lib/Phi/Widget.hs16
-rw-r--r--lib/Phi/Widgets/AlphaBox.hs4
-rw-r--r--lib/Phi/Widgets/Clock.hs6
-rw-r--r--lib/Phi/Widgets/Systray.hs6
-rw-r--r--lib/Phi/Widgets/Taskbar.hs8
8 files changed, 25 insertions, 25 deletions
diff --git a/lib/Phi/Border.hs b/lib/Phi/Border.hs
index 1c664db..0a9a74c 100644
--- a/lib/Phi/Border.hs
+++ b/lib/Phi/Border.hs
@@ -34,7 +34,7 @@ borderH bw = borderLeft bw + borderRight bw
borderV :: BorderWidth -> Int
borderV bw = borderTop bw + borderBottom bw
-data BorderState = BorderState [WidgetState] deriving Show
+data BorderState = BorderState ![WidgetState] deriving Show
data BorderConfig = BorderConfig { margin :: !BorderWidth
, borderWidth :: !Int
@@ -54,7 +54,7 @@ defaultBorderConfig = BorderConfig { margin = simpleBorderWidth 0
, borderWeight = 1
}
-data Border = Border BorderConfig [Widget] deriving Show
+data Border = Border !BorderConfig ![Widget] deriving Show
instance WidgetClass Border where
type WidgetData Border = BorderState
diff --git a/lib/Phi/Panel.hs b/lib/Phi/Panel.hs
index 72f6954..b847ff2 100644
--- a/lib/Phi/Panel.hs
+++ b/lib/Phi/Panel.hs
@@ -6,8 +6,8 @@ import Phi.Types
import Phi.Widget
-data PanelConfig = PanelConfig { panelPosition :: Position
- , panelSize :: Int
+data PanelConfig = PanelConfig { panelPosition :: !Position
+ , panelSize :: !Int
}
defaultPanelConfig :: PanelConfig
diff --git a/lib/Phi/Phi.hs b/lib/Phi/Phi.hs
index 94655d4..df71a1c 100644
--- a/lib/Phi/Phi.hs
+++ b/lib/Phi/Phi.hs
@@ -17,7 +17,7 @@ import Control.Monad.IO.Class
import Data.Typeable
-data Phi = Phi (TChan Message)
+data Phi = Phi !(TChan Message)
data Message = forall a. (Typeable a, Show a) => Message a
deriving instance Show Message
diff --git a/lib/Phi/Widget.hs b/lib/Phi/Widget.hs
index 0756e19..48c0b6c 100644
--- a/lib/Phi/Widget.hs
+++ b/lib/Phi/Widget.hs
@@ -29,7 +29,7 @@ import Phi.Phi
import Phi.X11.Atoms
-data Display = Display (MVar Xlib.Display) Atoms [(Xlib.Rectangle, Xlib.Window)]
+data Display = Display !(MVar Xlib.Display) !Atoms ![(Xlib.Rectangle, Xlib.Window)]
withDisplay :: MonadIO m => Display -> (Xlib.Display -> m a) -> m a
withDisplay (Display dispvar _ _) f = do
@@ -82,15 +82,15 @@ class Show a => WidgetClass a where
handleMessage :: a -> WidgetData a -> Message -> WidgetData a
handleMessage _ priv _ = priv
-data Widget = forall a. (WidgetClass a, Show (WidgetData a)) => Widget a
+data Widget = forall a. (WidgetClass a, Show (WidgetData a)) => Widget !a
deriving instance Show Widget
-data WidgetState = forall a. (WidgetClass a, Show (WidgetData a)) => WidgetState { stateWidget :: a
- , stateX :: Int
- , stateY :: Int
- , stateWidth :: Int
- , stateHeight :: Int
- , statePrivateData :: WidgetData a
+data WidgetState = forall a. (WidgetClass a, Show (WidgetData a)) => WidgetState { stateWidget :: !a
+ , stateX :: !Int
+ , stateY :: !Int
+ , stateWidth :: !Int
+ , stateHeight :: !Int
+ , statePrivateData :: !(WidgetData a)
}
deriving instance Show WidgetState
diff --git a/lib/Phi/Widgets/AlphaBox.hs b/lib/Phi/Widgets/AlphaBox.hs
index c09b911..dd4bfba 100644
--- a/lib/Phi/Widgets/AlphaBox.hs
+++ b/lib/Phi/Widgets/AlphaBox.hs
@@ -11,9 +11,9 @@ import Control.Monad
import Graphics.Rendering.Cairo
-data AlphaBoxState = AlphaBoxState [WidgetState] deriving Show
+data AlphaBoxState = AlphaBoxState ![WidgetState] deriving Show
-data AlphaBox = AlphaBox Double [Widget] deriving Show
+data AlphaBox = AlphaBox !Double ![Widget] deriving Show
instance WidgetClass AlphaBox where
diff --git a/lib/Phi/Widgets/Clock.hs b/lib/Phi/Widgets/Clock.hs
index 1f00bd0..d2ad134 100644
--- a/lib/Phi/Widgets/Clock.hs
+++ b/lib/Phi/Widgets/Clock.hs
@@ -34,11 +34,11 @@ data ClockConfig = ClockConfig { clockFormat :: !String
defaultClockConfig :: ClockConfig
defaultClockConfig = ClockConfig "%R" (0, 0, 0, 1) 0 50
-data Clock = Clock ClockConfig deriving Show
+data Clock = Clock !ClockConfig deriving Show
-data ClockState = ClockState ZonedTime deriving Show
+data ClockState = ClockState !ZonedTime deriving Show
-data ClockMessage = UpdateTime ZonedTime deriving (Show, Typeable)
+data ClockMessage = UpdateTime !ZonedTime deriving (Show, Typeable)
instance WidgetClass Clock where
type WidgetData Clock = ClockState
diff --git a/lib/Phi/Widgets/Systray.hs b/lib/Phi/Widgets/Systray.hs
index b8b85d7..385a740 100644
--- a/lib/Phi/Widgets/Systray.hs
+++ b/lib/Phi/Widgets/Systray.hs
@@ -45,13 +45,13 @@ instance Show (IORef a) where
show _ = "IORef <?>"
-data SystrayIconState = SystrayIconState Window Window deriving Show
+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] deriving Show
data Systray = Systray deriving Show
-data SystrayMessage = AddIcon Window Window | RemoveIcon Window | RenderIcon Window Window Int Int Int Int Bool
+data SystrayMessage = AddIcon !Window !Window | RemoveIcon !Window | RenderIcon !Window !Window !Int !Int !Int !Int !Bool
deriving (Show, Typeable)
diff --git a/lib/Phi/Widgets/Taskbar.hs b/lib/Phi/Widgets/Taskbar.hs
index a5a6fdc..e1a4adc 100644
--- a/lib/Phi/Widgets/Taskbar.hs
+++ b/lib/Phi/Widgets/Taskbar.hs
@@ -152,10 +152,10 @@ data WindowState = WindowState { windowTitle :: !String
, windowVisible :: !Bool
} deriving (Show, Eq)
-data TaskbarMessage = WindowListUpdate [Xlib.Window] (M.Map Window WindowState) (M.Map Window [(Int, Surface)]) (M.Map Window (IORef (Maybe (Int, Surface)))) (M.Map Window Xlib.Rectangle)
- | DesktopCountUpdate Int
- | CurrentDesktopUpdate Int
- | ActiveWindowUpdate Window
+data TaskbarMessage = WindowListUpdate ![Xlib.Window] !(M.Map Window WindowState) !(M.Map Window [(Int, Surface)]) !(M.Map Window (IORef (Maybe (Int, Surface)))) !(M.Map Window Xlib.Rectangle)
+ | DesktopCountUpdate !Int
+ | CurrentDesktopUpdate !Int
+ | ActiveWindowUpdate !Window
deriving (Show, Typeable)
instance Show (IORef a) where