This repository has been archived on 2025-03-02. You can view files and clone it, but cannot push or open issues or pull requests.
phi/lib/Phi/Widgets/Taskbar.hs

642 lines
27 KiB
Haskell
Raw Normal View History

{-# LANGUAGE MultiParamTypeClasses, DeriveDataTypeable, TypeSynonymInstances, FlexibleInstances #-}
2011-07-14 22:50:03 +02:00
2011-07-16 02:43:19 +02:00
module Phi.Widgets.Taskbar ( IconStyle
, idIconStyle
, desaturateIconStyle
, TaskStyle(..)
, DesktopStyle(..)
2011-07-16 02:43:19 +02:00
, TaskbarConfig(..)
2011-07-14 22:50:03 +02:00
, defaultTaskbarConfig
, Taskbar
2011-07-14 22:50:03 +02:00
, taskbar
) where
2011-09-07 19:35:59 +02:00
import Control.Arrow
2011-07-14 22:50:03 +02:00
import Control.Concurrent
import Control.Monad
import Control.Monad.State.Strict
2011-07-15 09:17:57 +02:00
import Control.Monad.Trans
2011-07-14 22:50:03 +02:00
2011-07-15 15:31:46 +02:00
import Data.Array.MArray
import Data.Bits
2011-07-15 09:17:57 +02:00
import Data.Char
2011-07-15 15:31:46 +02:00
import Data.Function
2011-07-18 00:59:40 +02:00
import Data.IORef
2011-07-15 15:31:46 +02:00
import Data.List
2011-07-15 09:17:57 +02:00
import Data.Maybe
2011-07-14 22:50:03 +02:00
import Data.Typeable
import Data.Unique
2011-07-15 15:31:46 +02:00
import Data.Word
import qualified Data.Accessor.Basic as A
import qualified Data.Accessor.Container as AC
2011-07-15 09:17:57 +02:00
import qualified Data.Map as M
2011-07-14 22:50:03 +02:00
2011-07-15 09:17:57 +02:00
import Foreign.C.Types
2011-07-14 22:50:03 +02:00
2011-07-15 09:17:57 +02:00
import Graphics.Rendering.Cairo
2011-07-14 22:50:03 +02:00
import Graphics.Rendering.Pango.Cairo
import Graphics.Rendering.Pango.Enums (PangoRectangle(..))
import Graphics.Rendering.Pango.Layout
2011-07-15 15:31:46 +02:00
import Graphics.Rendering.Pango.Font
2011-07-14 22:50:03 +02:00
2011-09-07 19:35:59 +02:00
import Graphics.XHB
import Graphics.XHB.Gen.Xproto
2011-07-15 09:17:57 +02:00
import Codec.Binary.UTF8.String
2011-07-14 22:50:03 +02:00
import Phi.Phi
import Phi.Types
2011-07-15 09:17:57 +02:00
import Phi.Border
2011-07-14 22:50:03 +02:00
import Phi.Widget
2011-07-15 09:17:57 +02:00
import Phi.X11.Atoms
2011-09-07 19:35:59 +02:00
import Phi.X11.Util
2011-07-14 22:50:03 +02:00
2011-08-22 21:10:59 +02:00
newtype IconStyle = IconStyle { withIconStyle :: Surface -> Render () }
instance Eq IconStyle where
_ == _ = True
2011-07-16 02:43:19 +02:00
idIconStyle :: IconStyle
2011-08-22 21:10:59 +02:00
idIconStyle = IconStyle $ flip withPatternForSurface setSource
2011-07-16 02:43:19 +02:00
desaturateIconStyle :: Double -> IconStyle
2011-08-22 21:10:59 +02:00
desaturateIconStyle v = IconStyle $ \icon -> do
2011-07-16 02:43:19 +02:00
w <- imageSurfaceGetWidth icon
h <- imageSurfaceGetHeight icon
2011-07-17 20:06:33 +02:00
renderWithSimilarSurface ContentColorAlpha w h $ \surface -> do
renderWith surface $ do
setOperator OperatorAdd
withPatternForSurface icon setSource
paint
2011-08-22 21:10:59 +02:00
2011-07-17 20:06:33 +02:00
setSourceRGB 0 0 0
paint
setOperator OperatorHslSaturation
setSourceRGBA 0 0 0 (1-v)
paint
2011-08-22 21:10:59 +02:00
2011-07-17 20:06:33 +02:00
setOperator OperatorDestIn
withPatternForSurface icon setSource
paint
2011-07-16 02:43:19 +02:00
2011-07-17 20:06:33 +02:00
withPatternForSurface surface setSource
2011-07-18 19:21:54 +02:00
2011-07-17 20:06:33 +02:00
downscaled :: Double -> Surface -> Render ()
downscaled s surface = do
2011-07-18 19:21:54 +02:00
case True of
_ | s < 0.5 -> do
w <- imageSurfaceGetWidth surface
h <- imageSurfaceGetHeight surface
renderWithSimilarSurface ContentColorAlpha (ceiling (fromIntegral w*s)) (ceiling (fromIntegral h*s)) $ \surface' -> do
renderWith surface' $ do
scale 0.5 0.5
downscaled (2*s) surface
paint
withPatternForSurface surface' setSource
2011-07-17 20:06:33 +02:00
2011-07-18 19:21:54 +02:00
| otherwise -> do
scale s s
withPatternForSurface surface setSource
2011-07-16 02:43:19 +02:00
data TaskStyle = TaskStyle { taskFont :: !String
, taskColor :: !Color
, taskBorder :: !BorderConfig
, taskIconStyle :: !IconStyle
2011-08-22 21:10:59 +02:00
} deriving Eq
2011-07-16 02:43:19 +02:00
data DesktopStyle = DesktopStyle { desktopFont :: !String
, desktopLabelWidth :: !Int
, desktopLabelGap :: !Int
, desktopColor :: !Color
, desktopBorder :: !BorderConfig
}
2011-07-16 02:43:19 +02:00
data TaskbarConfig = TaskbarConfig { taskMaxSize :: !Int
, normalTaskStyle :: !TaskStyle
, activeTaskStyle :: !TaskStyle
, desktopStyle :: !(Maybe (DesktopStyle, DesktopStyle))
}
2011-07-14 22:50:03 +02:00
2011-07-16 02:43:19 +02:00
defaultStyle :: TaskStyle
defaultStyle = TaskStyle { taskFont = "Sans 8"
, taskColor = (0, 0, 0, 1)
, taskBorder = defaultBorderConfig { backgroundColor = (0.75, 0.75, 0.75, 1) }
2011-07-16 02:43:19 +02:00
, taskIconStyle = idIconStyle
}
2011-07-14 22:50:03 +02:00
defaultTaskbarConfig :: TaskbarConfig
2011-07-18 00:59:40 +02:00
defaultTaskbarConfig = TaskbarConfig { taskMaxSize = 200
2011-07-16 02:43:19 +02:00
, normalTaskStyle = defaultStyle
, activeTaskStyle = defaultStyle {taskBorder = defaultBorderConfig { borderColor = (1, 1, 1, 1) }}
, desktopStyle = Nothing
2011-07-15 09:17:57 +02:00
}
2011-07-14 22:50:03 +02:00
data Taskbar = Taskbar TaskbarConfig
2011-07-15 15:31:46 +02:00
2011-09-07 19:35:59 +02:00
data TaskbarState = TaskbarState { taskbarScreens :: ![RECTANGLE]
, taskbarActiveWindow :: !WINDOW
2011-07-18 00:59:40 +02:00
, taskbarDesktopCount :: !Int
, taskbarCurrentDesktop :: !Int
, taskbarDesktopNames :: ![String]
2011-09-07 19:35:59 +02:00
, taskbarWindows :: ![WINDOW]
, taskbarWindowStates :: !(M.Map WINDOW WindowState)
} deriving Eq
data Icon = Icon !Unique !Int !Surface
instance Eq Icon where (Icon a _ _) == (Icon b _ _) = a == b
instance Show Icon where show (Icon _ size _) = "Icon { size = " ++ (show size) ++ " }"
createIcon :: Int -> Surface -> IO Icon
createIcon size surface = do
id <- newUnique
return $ Icon id size surface
2011-07-15 09:17:57 +02:00
2011-08-29 15:10:55 +02:00
data WindowState = WindowState { windowTitle :: !String
, windowDesktop :: !Int
, windowVisible :: !Bool
, windowIcons :: ![Icon]
2011-09-07 19:35:59 +02:00
, windowGeometry :: !RECTANGLE
} deriving (Eq, Show)
2011-08-22 21:10:59 +02:00
data WindowCache = WindowCache { createScaledIconCached :: !(IOCache ([Icon], Int) (Maybe Icon))
, renderWindowCached :: !(IOCache (String, Maybe Icon, TaskStyle, Int, Int) Surface)
}
2011-08-22 21:10:59 +02:00
createScaledIconCached' = A.fromSetGet (\a cache -> cache {createScaledIconCached = a}) createScaledIconCached
renderWindowCached' = A.fromSetGet (\a cache -> cache {renderWindowCached = a}) renderWindowCached
newtype DesktopCache = DesktopCache (IOCache () ())
emptyWindowCache :: WindowCache
emptyWindowCache = WindowCache { createScaledIconCached = createIOCache createScaledIcon
2011-08-22 21:10:59 +02:00
, renderWindowCached = createIOCache doRenderWindow
}
2011-08-22 21:10:59 +02:00
data TaskbarCache = TaskbarCache { desktopCaches :: !(M.Map Int DesktopCache)
2011-09-07 19:35:59 +02:00
, windowCaches :: !(M.Map WINDOW WindowCache)
2011-08-22 21:10:59 +02:00
}
-- substitute for the liftT function in Data.Accessor.MonadState that uses the strict StateT variant
liftT :: (Monad m) => A.T r s -> StateT s m a -> StateT r m a
liftT f m = do
s0 <- gets $ A.get f
(a,s1) <- lift $ runStateT m s0
modify $ A.set f s1
return a
liftIOStateT :: (MonadIO m) => StateT s IO a -> StateT s m a
liftIOStateT m = do
s0 <- get
(a,s1) <- liftIO $ runStateT m s0
put s1
return a
2011-08-22 21:10:59 +02:00
cached :: (MonadIO m, Eq a) => A.T s (IOCache a b) -> a -> StateT s m b
cached t = liftT t . liftIOStateT . runIOCache
2011-09-07 19:35:59 +02:00
data TaskbarMessage = WindowListUpdate ![WINDOW] !(M.Map WINDOW WindowState)
2011-08-12 03:18:46 +02:00
| DesktopCountUpdate !Int
| CurrentDesktopUpdate !Int
| DesktopNamesUpdate ![String]
2011-09-07 19:35:59 +02:00
| ActiveWindowUpdate !WINDOW
deriving (Typeable, Show)
2011-07-18 00:59:40 +02:00
2011-09-07 19:35:59 +02:00
instance Widget Taskbar TaskbarState (M.Map WINDOW WindowCache) where
2011-08-29 15:10:55 +02:00
initWidget (Taskbar _) phi dispvar screens = do
2011-08-12 02:11:09 +02:00
phi' <- dupPhi phi
forkIO $ taskbarRunner phi' dispvar
2011-07-15 09:17:57 +02:00
2011-09-07 19:35:59 +02:00
return $ TaskbarState (map fst screens) (fromXid xidNone) 0 (-1) [] [] M.empty
2011-08-21 21:39:26 +02:00
initCache _ = M.empty
2011-07-14 22:50:03 +02:00
minSize _ _ _ _ = 0
2011-07-14 22:50:03 +02:00
weight _ = 1
2011-08-29 15:10:55 +02:00
render (Taskbar config) TaskbarState { taskbarScreens = screens
, taskbarActiveWindow = activeWindow
2011-07-16 02:43:19 +02:00
, taskbarDesktopCount = desktopCount
, taskbarCurrentDesktop = currentDesktop
, taskbarDesktopNames = desktopNames
2011-07-16 02:43:19 +02:00
, taskbarWindows = windows
, taskbarWindowStates = windowStates
} _ _ w h screen = do
2011-08-29 15:10:55 +02:00
let windowScreen w = maximumBy (compare `on` unionArea (windowGeometry w)) screens
screenWindows = filter ((== Just screen) . fmap windowScreen . flip M.lookup windowStates) windows
desktopNumbers = take desktopCount $ zip [0..] (desktopNames ++ repeat "")
desktops = map (\desktop -> (desktop, filter (fromMaybe False . fmap (windowOnDesktop . fst $ desktop) . flip M.lookup windowStates) screenWindows)) desktopNumbers
windowCount = sum $ map (length . snd) $ desktops
dstyle d = fmap (if d == currentDesktop then snd else fst) $ desktopStyle config
dlabelwidth d = fromMaybe 0 $ fmap desktopLabelWidth $ dstyle d
gap d ds = if null (snd $ desktops !! d) then 0 else desktopLabelGap ds
dleftwidth d = fromMaybe 0 $ fmap (\ds@DesktopStyle {desktopBorder = border}
-> (borderLeft $ margin border) + (borderWidth border) + (borderLeft $ padding border)
+ dlabelwidth d + gap d ds) $ dstyle d
dwidth d = fromMaybe 0 $ fmap (\ds@DesktopStyle {desktopBorder = border}
-> (borderH $ margin border) + 2*(borderWidth border) + (borderH $ padding border)
+ dlabelwidth d + gap d ds) $ dstyle d
desktopsWidth = sum $ map (dwidth . fst) desktopNumbers
windowWidth = if windowCount == 0 then 0 else min (taskMaxSize config) ((w - desktopsWidth) `div` windowCount)
2011-08-21 21:39:26 +02:00
surface <- liftIO $ createImageSurface FormatARGB32 w h
cache <- liftM (M.filterWithKey $ \w _ -> elem w windows) get
cache' <- renderWith surface $ flip execStateT cache $ do
lift $ do
setOperator OperatorClear
paint
setOperator OperatorOver
2011-08-22 21:10:59 +02:00
flip (flip foldM_ 0) desktops $ \nwindows (desktop, desktopWindows) -> do
let dstyle' = dstyle (fst desktop)
dx = dleftwidth (fst desktop) + (sum $ map dwidth $ take (fst desktop) [0..]) + nwindows*windowWidth
case dstyle' of
Just ds -> do
let (r, g, b, a) = desktopColor ds
lift $ do
save
drawBorder (desktopBorder ds) (dx - dleftwidth (fst desktop)) 0 (dwidth (fst desktop) + windowWidth * length desktopWindows) h
clip
setSourceRGBA r g b a
renderText (desktopFont ds) (fromIntegral (dx - dlabelwidth (fst desktop) - gap (fst desktop) ds)) 0 (dlabelwidth (fst desktop)) h $ snd desktop
restore
forM_ (zip [0..] desktopWindows) $ \(i, window) -> do
let style = (if window == activeWindow then activeTaskStyle else normalTaskStyle) config
h' = h - (borderV $ margin $ desktopBorder ds) - 2*(borderWidth $ desktopBorder ds) - (borderV $ padding $ desktopBorder ds)
mstate = M.lookup window windowStates
x = dx + i*windowWidth
y = (borderTop $ margin $ desktopBorder ds) + (borderWidth $ desktopBorder ds) + (borderTop $ padding $ desktopBorder ds)
case mstate of
2011-08-22 21:10:59 +02:00
Just state -> do
windowSurface <- liftT (AC.mapDefault emptyWindowCache window) . liftIOStateT $ renderWindow state style windowWidth h'
lift $ do
save
translate (fromIntegral $ x - 5) (fromIntegral $ y - 5)
withPatternForSurface windowSurface setSource
paint
restore
Nothing -> return ()
_ -> return ()
2011-07-16 15:55:31 +02:00
return $ nwindows + length desktopWindows
put cache'
return [(True, SurfaceSlice 0 surface)]
2011-07-15 09:17:57 +02:00
handleMessage _ priv m = case (fromMessage m) of
Just (WindowListUpdate windows windowStates) -> priv { taskbarWindows = windows
, taskbarWindowStates = windowStates
}
2011-07-15 09:17:57 +02:00
Just (DesktopCountUpdate count) -> priv {taskbarDesktopCount = count}
Just (CurrentDesktopUpdate current) -> priv {taskbarCurrentDesktop = current}
Just (DesktopNamesUpdate names) -> priv {taskbarDesktopNames = names}
2011-07-15 09:17:57 +02:00
Just (ActiveWindowUpdate window) -> priv {taskbarActiveWindow = window}
2011-08-29 15:10:55 +02:00
_ -> case (fromMessage m) of
Just (UpdateScreens screens) -> priv {taskbarScreens = map fst screens}
_ -> priv
2011-07-15 09:17:57 +02:00
renderText :: String -> Int -> Int -> Int -> Int -> String -> Render ()
renderText font x y w h text = do
2011-07-15 15:31:46 +02:00
layout <- createLayout ""
(_, PangoRectangle _ _ textWidth textHeight) <- liftIO $ do
layoutSetMarkup layout $ "<span font='" ++ font ++ "'>" ++ (escapeMarkup text) ++ "</span>"
2011-07-15 15:31:46 +02:00
layoutSetWidth layout $ Just $ fromIntegral w
layoutSetEllipsize layout EllipsizeEnd
layoutGetExtents layout
moveTo ((fromIntegral x) + ((fromIntegral w) - textWidth)/2) ((fromIntegral y) + ((fromIntegral h) - textHeight)/2)
showLayout layout
2011-08-22 21:10:59 +02:00
renderWindow :: WindowState -> TaskStyle -> Int -> Int -> StateT WindowCache IO Surface
renderWindow state style w h = do
let h' = h - (borderV $ margin $ taskBorder style)
scaledIcon <- cached createScaledIconCached' (windowIcons state, h')
cached renderWindowCached' (windowTitle state, scaledIcon, style, w, h)
doRenderWindow :: (String, Maybe Icon, TaskStyle, Int, Int) -> IO Surface
doRenderWindow (title, scaledIcon, style, w, h) = do
let (r, g, b, a) = taskColor style
leftBorder = (borderLeft $ margin $ taskBorder style) + (borderWidth $ taskBorder style) + (borderLeft $ padding $ taskBorder style)
rightBorder = (borderRight $ margin $ taskBorder style) + (borderWidth $ taskBorder style) + (borderRight $ padding $ taskBorder style)
h' = h - (borderV $ margin $ taskBorder style)
2011-08-22 21:10:59 +02:00
surface <- createImageSurface FormatARGB32 (w+10) (h+10)
renderWith surface $ do
translate 5 5
save
2011-08-22 21:10:59 +02:00
drawBorder (taskBorder style) 0 0 w h
clip
setSourceRGBA r g b a
2011-08-22 21:10:59 +02:00
renderText (taskFont style) (fromIntegral (leftBorder + h' + 3)) 0 (w - leftBorder - h' - 3 - rightBorder) h title
restore
2011-08-22 21:10:59 +02:00
case scaledIcon of
Just (Icon _ _ icon) -> do
save
translate (fromIntegral leftBorder) (fromIntegral . borderTop . margin . taskBorder $ style)
withIconStyle (taskIconStyle style) icon
paint
restore
_ -> return ()
return surface
2011-08-22 21:10:59 +02:00
createScaledIcon :: ([Icon], Int) -> IO (Maybe Icon)
createScaledIcon (icons, h) = do
case bestIcon of
Just (Icon _ _ icon) -> do
scaledIcon <- createSimilarSurface icon ContentColorAlpha h h
renderWith scaledIcon $ do
imageW <- imageSurfaceGetWidth icon
imageH <- imageSurfaceGetHeight icon
let scalef = (fromIntegral h)/(fromIntegral $ max imageW imageH)
case () of
_ | imageH < imageW -> translate 0 (fromIntegral (imageW-imageH)*scalef/2)
| otherwise -> translate (fromIntegral (imageH-imageW)*scalef/2) 0
downscaled scalef icon
paint
2011-08-22 21:10:59 +02:00
fmap Just $ createIcon h scaledIcon
_ -> return Nothing
2011-07-16 01:28:47 +02:00
where
bestIcon = listToMaybe $ sortBy compareIcons icons
compareIcons = flip (compare `on` (\(Icon _ size _) -> size))
2011-07-15 15:31:46 +02:00
2011-07-15 09:17:57 +02:00
windowOnDesktop :: Int -> WindowState -> Bool
windowOnDesktop desktop state = (windowVisible state) && (desktop == windowDesktop state)
taskbarRunner :: Phi -> Display -> IO ()
taskbarRunner phi dispvar = do
(windows, states) <- liftIO $ withDisplay dispvar $ \disp -> do
2011-08-29 15:10:55 +02:00
(windows, states) <- getWindowStates disp (getAtoms dispvar) M.empty
2011-07-15 09:17:57 +02:00
desktopCount <- getDesktopCount disp (getAtoms dispvar)
current <- getCurrentDesktop disp (getAtoms dispvar)
names <- getDesktopNames disp (getAtoms dispvar)
2011-07-15 09:17:57 +02:00
activeWindow <- getActiveWindow disp (getAtoms dispvar)
sendMessage phi $ WindowListUpdate windows states
2011-07-15 09:17:57 +02:00
sendMessage phi $ DesktopCountUpdate desktopCount
sendMessage phi $ CurrentDesktopUpdate current
sendMessage phi $ DesktopNamesUpdate names
2011-07-15 09:17:57 +02:00
sendMessage phi $ ActiveWindowUpdate activeWindow
return (windows, states)
2011-07-15 09:17:57 +02:00
sendMessage phi Repaint
flip evalStateT (windows, states) $ forever $ do
2011-07-15 09:17:57 +02:00
m <- receiveMessage phi
case (fromMessage m) of
2011-09-07 19:35:59 +02:00
Just (XEvent event) ->
2011-07-16 15:55:31 +02:00
handleEvent phi dispvar event
2011-07-15 09:17:57 +02:00
_ ->
return ()
2011-07-15 15:31:46 +02:00
2011-09-07 19:35:59 +02:00
handleEvent :: Phi -> Display -> SomeEvent -> StateT ([WINDOW], M.Map WINDOW WindowState) IO ()
handleEvent phi dispvar event =
case (fromEvent event) of
Just e -> handlePropertyNotifyEvent phi dispvar e
Nothing -> case (fromEvent event) of
Just e -> handleConfigureNotifyEvent phi dispvar e
Nothing -> return ()
handlePropertyNotifyEvent :: Phi -> Display -> PropertyNotifyEvent -> StateT ([WINDOW], M.Map WINDOW WindowState) IO ()
handlePropertyNotifyEvent phi dispvar MkPropertyNotifyEvent {atom_PropertyNotifyEvent = atom, window_PropertyNotifyEvent = window} = do
2011-07-15 09:17:57 +02:00
let atoms = getAtoms dispvar
2011-09-07 19:35:59 +02:00
when (elem atom $ map ($ atoms) [ atom_NET_ACTIVE_WINDOW
, atom_NET_NUMBER_OF_DESKTOPS
, atom_NET_CURRENT_DESKTOP
, atom_NET_DESKTOP_NAMES
, atom_NET_CLIENT_LIST
, atom_NET_WM_ICON
, atomWM_NAME
, atom_NET_WM_NAME
, atom_NET_WM_DESKTOP
, atom_NET_WM_STATE
]) $ withDisplay dispvar $ \conn -> do
let rootwin = getRoot conn
2011-07-15 09:17:57 +02:00
if (window == rootwin)
then do
when (atom == atom_NET_ACTIVE_WINDOW atoms) $ do
2011-09-07 19:35:59 +02:00
activeWindow <- liftIO $ getActiveWindow conn atoms
2011-07-15 09:17:57 +02:00
sendMessage phi $ ActiveWindowUpdate activeWindow
sendMessage phi Repaint
when (atom == atom_NET_NUMBER_OF_DESKTOPS atoms) $ do
2011-09-07 19:35:59 +02:00
desktopCount <- liftIO $ getDesktopCount conn atoms
2011-07-15 09:17:57 +02:00
sendMessage phi $ DesktopCountUpdate desktopCount
sendMessage phi Repaint
when (atom == atom_NET_CURRENT_DESKTOP atoms) $ do
2011-09-07 19:35:59 +02:00
current <- liftIO $ getCurrentDesktop conn atoms
sendMessage phi $ CurrentDesktopUpdate current
sendMessage phi Repaint
when (atom == atom_NET_DESKTOP_NAMES atoms) $ do
2011-09-07 19:35:59 +02:00
names <- liftIO $ getDesktopNames conn atoms
sendMessage phi $ DesktopNamesUpdate names
sendMessage phi Repaint
2011-07-15 09:17:57 +02:00
when (atom == atom_NET_CLIENT_LIST atoms) $ do
(windows, windowStates) <- get
2011-09-07 19:35:59 +02:00
(windows', windowStates') <- liftIO $ getWindowStates conn atoms windowStates
2011-07-15 09:17:57 +02:00
2011-07-15 15:31:46 +02:00
when (windows /= windows') $ do
sendMessage phi $ WindowListUpdate windows' windowStates'
2011-07-15 09:17:57 +02:00
sendMessage phi Repaint
put (windows', windowStates')
2011-07-15 09:17:57 +02:00
else do
(windows, windowStates) <- get
2011-07-15 09:17:57 +02:00
when (elem window windows) $ do
case () of
_ | (atom == atom_NET_WM_ICON atoms) -> do
2011-09-07 19:35:59 +02:00
icons <- liftIO $ getWindowIcons conn atoms window
let windowStates' = M.update (\state -> Just state {windowIcons = icons}) window windowStates
sendMessage phi $ WindowListUpdate windows windowStates'
2011-07-15 15:31:46 +02:00
sendMessage phi Repaint
put (windows, windowStates')
| otherwise -> do
2011-09-07 19:35:59 +02:00
(name, desktop, visible) <- liftIO $ getWindowInfo conn atoms window
let mwindowState = M.lookup window windowStates
case mwindowState of
Just windowState -> do
let windowState' = windowState {windowTitle = name, windowDesktop = desktop, windowVisible = visible}
when (windowState /= windowState') $ do
let windowStates' = M.insert window windowState' windowStates
sendMessage phi $ WindowListUpdate windows windowStates'
sendMessage phi Repaint
put (windows, windowStates')
Nothing ->
return ()
2011-07-16 15:55:31 +02:00
2011-09-07 19:35:59 +02:00
handleConfigureNotifyEvent :: Phi -> Display -> ConfigureNotifyEvent -> StateT ([WINDOW], M.Map WINDOW WindowState) IO ()
handleConfigureNotifyEvent phi dispvar MkConfigureNotifyEvent {window_ConfigureNotifyEvent = window} = do
(windows, windowStates) <- get
2011-09-07 19:35:59 +02:00
when (elem window windows) $ withDisplay dispvar $ \conn -> do
let geom = fmap windowGeometry . M.lookup window $ windowStates
geom' <- liftIO $ getWindowGeometry conn window
2011-08-29 15:10:55 +02:00
when (geom /= (Just geom')) $ do
let windowStates' = M.update (\state -> Just state {windowGeometry = geom'}) window windowStates
sendMessage phi $ WindowListUpdate windows windowStates'
2011-07-16 15:55:31 +02:00
sendMessage phi Repaint
put (windows, windowStates')
2011-07-16 15:55:31 +02:00
2011-09-07 19:35:59 +02:00
getDesktopCount :: Connection -> Atoms -> IO Int
getDesktopCount conn atoms =
liftM (fromIntegral . fromMaybe 0 . join . fmap listToMaybe) $ getProperty32 conn (getRoot conn) (atom_NET_NUMBER_OF_DESKTOPS atoms)
2011-07-15 09:17:57 +02:00
2011-09-07 19:35:59 +02:00
getCurrentDesktop :: Connection -> Atoms -> IO Int
getCurrentDesktop conn atoms =
liftM (fromIntegral . fromMaybe (-1) . join . fmap listToMaybe) $ getProperty32 conn (getRoot conn) (atom_NET_CURRENT_DESKTOP atoms)
2011-07-15 09:17:57 +02:00
2011-09-07 19:35:59 +02:00
getDesktopNames :: Connection -> Atoms -> IO [String]
getDesktopNames conn atoms =
liftM (map (decode . map fromIntegral) . break' . fromMaybe []) $ getProperty8 conn (getRoot conn) (atom_NET_DESKTOP_NAMES atoms)
where
break' l = case dropWhile (== 0) l of
[] -> []
l' -> w : break' l''
where (w, l'') = break (== 0) l'
2011-09-07 19:35:59 +02:00
getActiveWindow :: Connection -> Atoms -> IO WINDOW
getActiveWindow conn atoms =
liftM (fromXid . toXid . fromMaybe 0 . join . fmap listToMaybe) $ getProperty32 conn (getRoot conn) (atom_NET_ACTIVE_WINDOW atoms)
2011-07-15 09:17:57 +02:00
2011-09-07 19:35:59 +02:00
getWindowStates :: Connection -> Atoms -> M.Map WINDOW WindowState -> IO ([WINDOW], M.Map WINDOW WindowState)
getWindowStates conn atoms windowStates = do
windows <- getWindowList conn atoms
2011-07-15 09:17:57 +02:00
let windowStates' = map (\w -> (w, M.lookup w windowStates)) windows
newWindowStates <- mapM getWindowState' windowStates'
return (windows, M.fromList newWindowStates)
2011-07-15 09:17:57 +02:00
where
getWindowState' (window, Just windowState) = return (window, windowState)
getWindowState' (window, Nothing) = do
2011-09-07 19:35:59 +02:00
changeWindowAttributes conn window $ toValueParam [(CWEventMask, toMask [EventMaskPropertyChange, EventMaskStructureNotify])]
windowState <- getWindowState conn atoms window
2011-07-15 09:17:57 +02:00
return (window, windowState)
2011-09-07 19:35:59 +02:00
getWindowState :: Connection -> Atoms -> WINDOW -> IO WindowState
getWindowState conn atoms window = do
(name, workspace, visible) <- getWindowInfo conn atoms window
icons <- getWindowIcons conn atoms window
geom <- getWindowGeometry conn window
return $ WindowState { windowTitle = name
, windowDesktop = workspace
, windowVisible = visible
, windowIcons = icons
2011-08-29 15:10:55 +02:00
, windowGeometry = geom
}
2011-09-07 19:35:59 +02:00
getWindowInfo :: Connection -> Atoms -> WINDOW -> IO (String, Int, Bool)
getWindowInfo conn atoms window = do
netwmname <- liftM (fmap (decode . map fromIntegral)) $ getProperty8 conn window (atom_NET_WM_NAME atoms)
2011-07-15 09:17:57 +02:00
wmname <- case netwmname of
Just name -> return name
2011-09-07 19:35:59 +02:00
Nothing -> liftM (map unsignedChr . fromMaybe []) $ getProperty8 conn window (atom_NET_WM_NAME atoms)
2011-07-15 09:17:57 +02:00
2011-09-07 19:35:59 +02:00
workspace <- liftM (fromIntegral . fromMaybe 0xFFFFFFFF . join . fmap listToMaybe) $ getProperty32 conn window (atom_NET_WM_DESKTOP atoms)
visible <- showWindow conn atoms window
2011-07-15 09:17:57 +02:00
return (wmname, workspace, visible)
2011-07-15 09:17:57 +02:00
where
2011-09-07 19:35:59 +02:00
unsignedChr = chr . fromIntegral
2011-07-15 09:17:57 +02:00
2011-09-07 19:35:59 +02:00
getWindowIcons :: Connection -> Atoms -> WINDOW -> IO [Icon]
getWindowIcons conn atoms window = getProperty32 conn window (atom_NET_WM_ICON atoms) >>= readIcons . fromMaybe []
2011-07-15 15:31:46 +02:00
2011-07-16 15:55:31 +02:00
2011-09-07 19:35:59 +02:00
readIcons :: [Word32] -> IO [Icon]
2011-07-15 15:31:46 +02:00
readIcons (width:height:iconData) = do
if ((fromIntegral $ length iconData) < (width*height)) then return [] else do
let (thisIcon, rest) = splitAt (fromIntegral (width*height)) iconData
surface <- createImageSurface FormatARGB32 (fromIntegral width) (fromIntegral height)
surfaceData <- imageSurfaceGetPixels surface :: IO (SurfaceData Int Word32)
2011-07-17 19:20:19 +02:00
forM_ (zip thisIcon [0..]) $ \(e, i) -> writeArray surfaceData i $ premultiply $ fromIntegral e
2011-07-15 15:31:46 +02:00
surfaceMarkDirty surface
liftM2 (:) (createIcon (fromIntegral $ max width height) surface) (readIcons rest)
2011-07-15 15:31:46 +02:00
readIcons _ = return []
premultiply :: Word32 -> Word32
premultiply c = a .|. r .|. g .|. b
where
amask = 0xFF000000
rmask = 0x00FF0000
gmask = 0x0000FF00
bmask = 0x000000FF
a = c .&. amask
pm mask = (((c .&. mask) * (a `shiftR` 24)) `div` 0xFF) .&. mask
r = pm rmask
g = pm gmask
b = pm bmask
2011-07-16 15:55:31 +02:00
2011-09-07 19:35:59 +02:00
getWindowGeometry :: Connection -> WINDOW -> IO RECTANGLE
getWindowGeometry conn window =
getGeometry conn (fromXid . toXid $ window) >>= getReply >>= return . ((const $ MkRECTANGLE 0 0 0 0) ||| (\(MkGetGeometryReply _ _ x y width height _) -> MkRECTANGLE x y width height))
2011-07-16 15:55:31 +02:00
2011-09-07 19:35:59 +02:00
showWindow :: Connection -> Atoms -> WINDOW -> IO Bool
showWindow conn atoms window = do
states <- liftM (map (fromXid . toXid) . fromMaybe []) $ getProperty32 conn window (atom_NET_WM_STATE atoms)
transientFor <- liftM (map fromIntegral . fromMaybe []) $ getProperty32 conn window (atomWM_TRANSIENT_FOR atoms)
windowType <- liftM (fromMaybe (atom_NET_WM_WINDOW_TYPE_NORMAL atoms) . fmap (fromXid . toXid) . join . fmap listToMaybe) $
getProperty32 conn window (atom_NET_WM_STATE atoms)
2011-07-15 09:17:57 +02:00
return $ not $ or [ elem (atom_NET_WM_STATE_SKIP_TASKBAR atoms) states
2011-09-07 19:35:59 +02:00
, transientFor /= [] && transientFor /= [0]
2011-07-15 09:17:57 +02:00
, elem windowType $ map ($ atoms) [ atom_NET_WM_WINDOW_TYPE_DOCK
, atom_NET_WM_WINDOW_TYPE_DESKTOP
, atom_NET_WM_WINDOW_TYPE_TOOLBAR
, atom_NET_WM_WINDOW_TYPE_MENU
, atom_NET_WM_WINDOW_TYPE_SPLASH
]
]
2011-07-15 15:31:46 +02:00
2011-07-15 09:17:57 +02:00
2011-09-07 19:35:59 +02:00
getWindowList :: Connection -> Atoms -> IO [WINDOW]
getWindowList conn atoms = liftM (map (fromXid . toXid) . join . maybeToList) $ getProperty32 conn (getRoot conn) (atom_NET_CLIENT_LIST atoms)
2011-07-14 22:50:03 +02:00
taskbar :: TaskbarConfig -> Taskbar
taskbar = Taskbar