Make taskbar more styleable
This commit is contained in:
parent
9945e23251
commit
3f4007681a
2 changed files with 89 additions and 27 deletions
|
@ -1,6 +1,10 @@
|
||||||
{-# LANGUAGE TypeFamilies, DeriveDataTypeable #-}
|
{-# LANGUAGE TypeFamilies, DeriveDataTypeable, TypeSynonymInstances #-}
|
||||||
|
|
||||||
module Phi.Widgets.Taskbar ( TaskbarConfig(..)
|
module Phi.Widgets.Taskbar ( IconStyle
|
||||||
|
, idIconStyle
|
||||||
|
, desaturateIconStyle
|
||||||
|
, TaskStyle(..)
|
||||||
|
, TaskbarConfig(..)
|
||||||
, defaultTaskbarConfig
|
, defaultTaskbarConfig
|
||||||
, taskbar
|
, taskbar
|
||||||
) where
|
) where
|
||||||
|
@ -41,19 +45,62 @@ import Phi.Widget
|
||||||
import Phi.X11.Atoms
|
import Phi.X11.Atoms
|
||||||
|
|
||||||
|
|
||||||
data TaskbarConfig = TaskbarConfig { taskbarFont :: !String
|
type IconStyle = Surface -> Render ()
|
||||||
, taskMaxSize :: !Int
|
instance Show IconStyle where
|
||||||
|
show _ = "IconStyle"
|
||||||
|
|
||||||
|
idIconStyle :: IconStyle
|
||||||
|
idIconStyle = flip withPatternForSurface setSource
|
||||||
|
|
||||||
|
desaturateIconStyle :: Double -> IconStyle
|
||||||
|
desaturateIconStyle v icon = do
|
||||||
|
w <- imageSurfaceGetWidth icon
|
||||||
|
h <- imageSurfaceGetHeight icon
|
||||||
|
|
||||||
|
renderWithSimilarSurface ContentColorAlpha w h $ \surface1 -> do
|
||||||
|
renderWithSimilarSurface ContentColor w h $ \surface2 -> do
|
||||||
|
renderWith surface1 $ do
|
||||||
|
renderWith surface2 $ do
|
||||||
|
withPatternForSurface icon setSource
|
||||||
|
paint
|
||||||
|
|
||||||
|
setOperator OperatorHslSaturation
|
||||||
|
setSourceRGBA 0 0 0 (1-v)
|
||||||
|
paint
|
||||||
|
|
||||||
|
withPatternForSurface surface2 setSource
|
||||||
|
paint
|
||||||
|
|
||||||
|
setOperator OperatorDestIn
|
||||||
|
withPatternForSurface icon setSource
|
||||||
|
paint
|
||||||
|
|
||||||
|
withPatternForSurface surface1 setSource
|
||||||
|
|
||||||
|
data TaskStyle = TaskStyle { taskFont :: !String
|
||||||
|
, taskColor :: !Color
|
||||||
|
, taskBorder :: !BorderConfig
|
||||||
|
, taskIconStyle :: !IconStyle
|
||||||
|
} deriving Show
|
||||||
|
|
||||||
|
data TaskbarConfig = TaskbarConfig { taskMaxSize :: !Int
|
||||||
, showDesktops :: !Bool
|
, showDesktops :: !Bool
|
||||||
, taskBorder :: !BorderConfig
|
, normalTaskStyle :: !TaskStyle
|
||||||
, activeTaskBorder :: !BorderConfig
|
, activeTaskStyle :: !TaskStyle
|
||||||
} deriving Show
|
} deriving Show
|
||||||
|
|
||||||
|
defaultStyle :: TaskStyle
|
||||||
|
defaultStyle = TaskStyle { taskFont = "Sans 8"
|
||||||
|
, taskColor = (0, 0, 0, 1)
|
||||||
|
, taskBorder = defaultBorderConfig
|
||||||
|
, taskIconStyle = idIconStyle
|
||||||
|
}
|
||||||
|
|
||||||
defaultTaskbarConfig :: TaskbarConfig
|
defaultTaskbarConfig :: TaskbarConfig
|
||||||
defaultTaskbarConfig = TaskbarConfig { taskbarFont = "Sans 7"
|
defaultTaskbarConfig = TaskbarConfig { taskMaxSize = 150
|
||||||
, taskMaxSize = 150
|
|
||||||
, showDesktops = False
|
, showDesktops = False
|
||||||
, taskBorder = defaultBorderConfig
|
, normalTaskStyle = defaultStyle
|
||||||
, activeTaskBorder = defaultBorderConfig { borderColor = (1, 1, 1, 1) }
|
, activeTaskStyle = defaultStyle {taskBorder = defaultBorderConfig { borderColor = (1, 1, 1, 1) }}
|
||||||
}
|
}
|
||||||
|
|
||||||
data Taskbar = Taskbar TaskbarConfig deriving Show
|
data Taskbar = Taskbar TaskbarConfig deriving Show
|
||||||
|
@ -90,35 +137,41 @@ instance WidgetClass Taskbar where
|
||||||
minSize _ = 0
|
minSize _ = 0
|
||||||
weight _ = 1
|
weight _ = 1
|
||||||
|
|
||||||
render (Taskbar config) TaskbarState {taskbarActiveWindow = activeWindow, taskbarDesktopCount = desktopCount, taskbarWindows = windows, taskbarWindowStates = windowStates, taskbarWindowIcons = windowIcons} w h = do
|
render (Taskbar config) TaskbarState { taskbarActiveWindow = activeWindow
|
||||||
|
, taskbarDesktopCount = desktopCount
|
||||||
|
, taskbarWindows = windows
|
||||||
|
, taskbarWindowStates = windowStates
|
||||||
|
, taskbarWindowIcons = windowIcons
|
||||||
|
} w h = do
|
||||||
let desktopWindows = map (\desktop -> (desktop, filter (fromMaybe False . fmap (windowOnDesktop desktop) . flip M.lookup windowStates) windows)) $ take desktopCount [0..]
|
let desktopWindows = map (\desktop -> (desktop, filter (fromMaybe False . fmap (windowOnDesktop desktop) . flip M.lookup windowStates) windows)) $ take desktopCount [0..]
|
||||||
windowCount = sum $ map (length . snd) $ desktopWindows
|
windowCount = sum $ map (length . snd) $ desktopWindows
|
||||||
when (windowCount /= 0) $ do
|
when (windowCount /= 0) $ do
|
||||||
let windowWidth = min (taskMaxSize config) (w `div` windowCount)
|
let windowWidth = min (taskMaxSize config) (w `div` windowCount)
|
||||||
|
|
||||||
forM_ (zip [0..] $ join $ map snd desktopWindows) $ \(i, window) -> do
|
forM_ (zip [0..] $ join $ map snd desktopWindows) $ \(i, window) -> do
|
||||||
let border = if window == activeWindow then activeTaskBorder config else taskBorder config
|
let style = (if window == activeWindow then activeTaskStyle else normalTaskStyle) config
|
||||||
leftBorder = (borderLeft $ margin border) + (borderWidth border) + (borderLeft $ padding border)
|
(r, g, b, a) = taskColor style
|
||||||
rightBorder = (borderRight $ margin border) + (borderWidth border) + (borderRight $ padding border)
|
leftBorder = (borderLeft $ margin $ taskBorder style) + (borderWidth $ taskBorder style) + (borderLeft $ padding $ taskBorder style)
|
||||||
h' = h - (borderV $ margin border)
|
rightBorder = (borderRight $ margin $ taskBorder style) + (borderWidth $ taskBorder style) + (borderRight $ padding $ taskBorder style)
|
||||||
|
h' = h - (borderV $ margin $ taskBorder style)
|
||||||
mstate = M.lookup window windowStates
|
mstate = M.lookup window windowStates
|
||||||
micons = M.lookup window windowIcons
|
micons = M.lookup window windowIcons
|
||||||
|
|
||||||
case (mstate, micons) of
|
case (mstate, micons) of
|
||||||
(Just state, Just icons) -> do
|
(Just state, Just icons) -> do
|
||||||
save
|
save
|
||||||
drawBorder border (i*windowWidth) 0 windowWidth h
|
drawBorder (taskBorder style) (i*windowWidth) 0 windowWidth h
|
||||||
clip
|
clip
|
||||||
|
|
||||||
setSourceRGB 1 1 1
|
setSourceRGBA r g b a
|
||||||
renderText config (fromIntegral (i*windowWidth + leftBorder + h' + 3)) 0 (windowWidth - leftBorder - h' - 3 - rightBorder) h $ windowTitle state
|
renderText style (fromIntegral (i*windowWidth + leftBorder + h' + 3)) 0 (windowWidth - leftBorder - h' - 3 - rightBorder) h $ windowTitle state
|
||||||
|
|
||||||
restore
|
restore
|
||||||
|
|
||||||
case bestIcon h' icons of
|
case bestIcon h' icons of
|
||||||
Just icon -> withPatternForSurface icon $ \pattern -> do
|
Just icon -> do
|
||||||
save
|
save
|
||||||
translate (fromIntegral $ i*windowWidth + leftBorder) (fromIntegral $ borderTop $ margin border)
|
translate (fromIntegral $ i*windowWidth + leftBorder) (fromIntegral $ borderTop $ margin $ taskBorder style)
|
||||||
imageW <- imageSurfaceGetWidth icon
|
imageW <- imageSurfaceGetWidth icon
|
||||||
imageH <- imageSurfaceGetHeight icon
|
imageH <- imageSurfaceGetHeight icon
|
||||||
|
|
||||||
|
@ -127,8 +180,8 @@ instance WidgetClass Taskbar where
|
||||||
|
|
||||||
when (imageH < imageW) $
|
when (imageH < imageW) $
|
||||||
translate 0 $ (fromIntegral (imageW-imageH))/2
|
translate 0 $ (fromIntegral (imageW-imageH))/2
|
||||||
|
|
||||||
setSource pattern
|
taskIconStyle style icon
|
||||||
paint
|
paint
|
||||||
restore
|
restore
|
||||||
|
|
||||||
|
@ -144,11 +197,11 @@ instance WidgetClass Taskbar where
|
||||||
_ -> priv
|
_ -> priv
|
||||||
|
|
||||||
|
|
||||||
renderText :: TaskbarConfig -> Int -> Int -> Int -> Int -> String -> Render ()
|
renderText :: TaskStyle -> Int -> Int -> Int -> Int -> String -> Render ()
|
||||||
renderText config x y w h text = do
|
renderText style x y w h text = do
|
||||||
layout <- createLayout ""
|
layout <- createLayout ""
|
||||||
(_, PangoRectangle _ _ textWidth textHeight) <- liftIO $ do
|
(_, PangoRectangle _ _ textWidth textHeight) <- liftIO $ do
|
||||||
layoutSetMarkup layout $ "<span font='" ++ (taskbarFont config) ++ "'>" ++ (escapeMarkup text) ++ "</span>"
|
layoutSetMarkup layout $ "<span font='" ++ (taskFont style) ++ "'>" ++ (escapeMarkup text) ++ "</span>"
|
||||||
layoutSetWidth layout $ Just $ fromIntegral w
|
layoutSetWidth layout $ Just $ fromIntegral w
|
||||||
layoutSetEllipsize layout EllipsizeEnd
|
layoutSetEllipsize layout EllipsizeEnd
|
||||||
|
|
||||||
|
|
13
src/Phi.hs
13
src/Phi.hs
|
@ -12,9 +12,18 @@ main = do
|
||||||
runPhi defaultXConfig defaultPanelConfig { panelPosition = Bottom }
|
runPhi defaultXConfig defaultPanelConfig { panelPosition = Bottom }
|
||||||
[theTaskbar, brightBorder [theClock]]
|
[theTaskbar, brightBorder [theClock]]
|
||||||
where
|
where
|
||||||
theTaskbar = taskbar defaultTaskbarConfig { taskBorder = BorderConfig (BorderWidth 2 4 2 4) 1 (BorderWidth 0 5 0 5) (0.9, 0.9, 0.9, 0.65) (0.45, 0.45, 0.45, 0.8) 5 0
|
normalTaskBorder = BorderConfig (BorderWidth 2 4 2 4) 1 (BorderWidth 0 5 0 5) (0.9, 0.9, 0.9, 0.65) (0.45, 0.45, 0.45, 0.8) 5 0
|
||||||
, activeTaskBorder = BorderConfig (BorderWidth 2 4 2 4) 1 (BorderWidth 0 5 0 5) (1, 1, 1, 0.65) (0, 0, 0, 0.8) 5 0
|
activeTaskBorder = normalTaskBorder {borderColor = (1, 1, 1, 0.65), backgroundColor = (0, 0, 0, 0.8)}
|
||||||
|
taskStyle = TaskStyle { taskFont = "Sans 7"
|
||||||
|
, taskColor = (1, 1, 1, 1)
|
||||||
|
, taskBorder = normalTaskBorder
|
||||||
|
, taskIconStyle = idIconStyle
|
||||||
|
}
|
||||||
|
|
||||||
|
theTaskbar = taskbar defaultTaskbarConfig { normalTaskStyle = taskStyle {taskIconStyle = desaturateIconStyle 0.7}
|
||||||
|
, activeTaskStyle = taskStyle {taskBorder = activeTaskBorder}
|
||||||
}
|
}
|
||||||
|
|
||||||
theClock = clock defaultClockConfig { clockFormat = "<span font='Sans 8'>%R</span>\n<span font='Sans 6'>%A %d %B</span>"
|
theClock = clock defaultClockConfig { clockFormat = "<span font='Sans 8'>%R</span>\n<span font='Sans 6'>%A %d %B</span>"
|
||||||
, lineSpacing = (-2)
|
, lineSpacing = (-2)
|
||||||
, clockSize = 75
|
, clockSize = 75
|
||||||
|
|
Reference in a new issue