Some strictness optimizations
This commit is contained in:
parent
180285af85
commit
15bccc001a
8 changed files with 25 additions and 25 deletions
|
@ -34,7 +34,7 @@ borderH bw = borderLeft bw + borderRight bw
|
||||||
borderV :: BorderWidth -> Int
|
borderV :: BorderWidth -> Int
|
||||||
borderV bw = borderTop bw + borderBottom bw
|
borderV bw = borderTop bw + borderBottom bw
|
||||||
|
|
||||||
data BorderState = BorderState [WidgetState] deriving Show
|
data BorderState = BorderState ![WidgetState] deriving Show
|
||||||
|
|
||||||
data BorderConfig = BorderConfig { margin :: !BorderWidth
|
data BorderConfig = BorderConfig { margin :: !BorderWidth
|
||||||
, borderWidth :: !Int
|
, borderWidth :: !Int
|
||||||
|
@ -54,7 +54,7 @@ defaultBorderConfig = BorderConfig { margin = simpleBorderWidth 0
|
||||||
, borderWeight = 1
|
, borderWeight = 1
|
||||||
}
|
}
|
||||||
|
|
||||||
data Border = Border BorderConfig [Widget] deriving Show
|
data Border = Border !BorderConfig ![Widget] deriving Show
|
||||||
|
|
||||||
instance WidgetClass Border where
|
instance WidgetClass Border where
|
||||||
type WidgetData Border = BorderState
|
type WidgetData Border = BorderState
|
||||||
|
|
|
@ -6,8 +6,8 @@ import Phi.Types
|
||||||
import Phi.Widget
|
import Phi.Widget
|
||||||
|
|
||||||
|
|
||||||
data PanelConfig = PanelConfig { panelPosition :: Position
|
data PanelConfig = PanelConfig { panelPosition :: !Position
|
||||||
, panelSize :: Int
|
, panelSize :: !Int
|
||||||
}
|
}
|
||||||
|
|
||||||
defaultPanelConfig :: PanelConfig
|
defaultPanelConfig :: PanelConfig
|
||||||
|
|
|
@ -17,7 +17,7 @@ import Control.Monad.IO.Class
|
||||||
|
|
||||||
import Data.Typeable
|
import Data.Typeable
|
||||||
|
|
||||||
data Phi = Phi (TChan Message)
|
data Phi = Phi !(TChan Message)
|
||||||
|
|
||||||
data Message = forall a. (Typeable a, Show a) => Message a
|
data Message = forall a. (Typeable a, Show a) => Message a
|
||||||
deriving instance Show Message
|
deriving instance Show Message
|
||||||
|
|
|
@ -29,7 +29,7 @@ import Phi.Phi
|
||||||
import Phi.X11.Atoms
|
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 :: MonadIO m => Display -> (Xlib.Display -> m a) -> m a
|
||||||
withDisplay (Display dispvar _ _) f = do
|
withDisplay (Display dispvar _ _) f = do
|
||||||
|
@ -82,15 +82,15 @@ class Show a => WidgetClass a where
|
||||||
handleMessage :: a -> WidgetData a -> Message -> WidgetData a
|
handleMessage :: a -> WidgetData a -> Message -> WidgetData a
|
||||||
handleMessage _ priv _ = priv
|
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
|
deriving instance Show Widget
|
||||||
|
|
||||||
data WidgetState = forall a. (WidgetClass a, Show (WidgetData a)) => WidgetState { stateWidget :: a
|
data WidgetState = forall a. (WidgetClass a, Show (WidgetData a)) => WidgetState { stateWidget :: !a
|
||||||
, stateX :: Int
|
, stateX :: !Int
|
||||||
, stateY :: Int
|
, stateY :: !Int
|
||||||
, stateWidth :: Int
|
, stateWidth :: !Int
|
||||||
, stateHeight :: Int
|
, stateHeight :: !Int
|
||||||
, statePrivateData :: WidgetData a
|
, statePrivateData :: !(WidgetData a)
|
||||||
}
|
}
|
||||||
deriving instance Show WidgetState
|
deriving instance Show WidgetState
|
||||||
|
|
||||||
|
|
|
@ -11,9 +11,9 @@ import Control.Monad
|
||||||
import Graphics.Rendering.Cairo
|
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
|
instance WidgetClass AlphaBox where
|
||||||
|
|
|
@ -34,11 +34,11 @@ data ClockConfig = ClockConfig { clockFormat :: !String
|
||||||
defaultClockConfig :: ClockConfig
|
defaultClockConfig :: ClockConfig
|
||||||
defaultClockConfig = ClockConfig "%R" (0, 0, 0, 1) 0 50
|
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
|
instance WidgetClass Clock where
|
||||||
type WidgetData Clock = ClockState
|
type WidgetData Clock = ClockState
|
||||||
|
|
|
@ -45,13 +45,13 @@ instance Show (IORef a) where
|
||||||
show _ = "IORef <?>"
|
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 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)
|
deriving (Show, Typeable)
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -152,10 +152,10 @@ data WindowState = WindowState { windowTitle :: !String
|
||||||
, windowVisible :: !Bool
|
, windowVisible :: !Bool
|
||||||
} deriving (Show, Eq)
|
} 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)
|
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
|
| DesktopCountUpdate !Int
|
||||||
| CurrentDesktopUpdate Int
|
| CurrentDesktopUpdate !Int
|
||||||
| ActiveWindowUpdate Window
|
| ActiveWindowUpdate !Window
|
||||||
deriving (Show, Typeable)
|
deriving (Show, Typeable)
|
||||||
|
|
||||||
instance Show (IORef a) where
|
instance Show (IORef a) where
|
||||||
|
|
Reference in a new issue