2011-07-16 02:43:19 +02:00
|
|
|
{-# LANGUAGE TypeFamilies, DeriveDataTypeable, TypeSynonymInstances #-}
|
2011-07-14 22:50:03 +02:00
|
|
|
|
2011-07-16 02:43:19 +02:00
|
|
|
module Phi.Widgets.Taskbar ( IconStyle
|
|
|
|
, idIconStyle
|
|
|
|
, desaturateIconStyle
|
|
|
|
, TaskStyle(..)
|
2011-07-16 10:46:26 +02:00
|
|
|
, DesktopStyle(..)
|
2011-07-16 02:43:19 +02:00
|
|
|
, TaskbarConfig(..)
|
2011-07-14 22:50:03 +02:00
|
|
|
, defaultTaskbarConfig
|
|
|
|
, taskbar
|
|
|
|
) where
|
|
|
|
|
|
|
|
import Control.Concurrent
|
|
|
|
import Control.Monad
|
2011-07-15 09:17:57 +02:00
|
|
|
import Control.Monad.State
|
|
|
|
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
|
2011-07-15 15:31:46 +02:00
|
|
|
import Data.Word
|
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-07-15 09:17:57 +02:00
|
|
|
import Graphics.X11.Xlib (Window)
|
|
|
|
import qualified Graphics.X11.Xlib as Xlib
|
|
|
|
import qualified Graphics.X11.Xlib.Extras as XExtras
|
|
|
|
|
|
|
|
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-07-14 22:50:03 +02:00
|
|
|
|
|
|
|
|
2011-07-16 02:43:19 +02:00
|
|
|
type IconStyle = Surface -> Render ()
|
|
|
|
instance Show IconStyle where
|
2011-07-16 10:46:26 +02:00
|
|
|
show _ = "IconStyle <?>"
|
2011-07-16 02:43:19 +02:00
|
|
|
|
|
|
|
idIconStyle :: IconStyle
|
|
|
|
idIconStyle = flip withPatternForSurface setSource
|
|
|
|
|
|
|
|
desaturateIconStyle :: Double -> IconStyle
|
|
|
|
desaturateIconStyle v icon = do
|
|
|
|
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
|
|
|
|
|
|
|
|
setSourceRGB 0 0 0
|
|
|
|
paint
|
|
|
|
|
|
|
|
setOperator OperatorHslSaturation
|
|
|
|
setSourceRGBA 0 0 0 (1-v)
|
|
|
|
paint
|
2011-07-16 02:43:19 +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
|
|
|
|
|
|
|
|
downscaled :: Double -> Surface -> Render ()
|
|
|
|
downscaled s surface = do
|
|
|
|
case True of
|
|
|
|
_ | s < 0.5 -> do
|
|
|
|
w <- imageSurfaceGetWidth surface
|
|
|
|
h <- imageSurfaceGetHeight surface
|
|
|
|
|
2011-07-17 20:54:49 +02:00
|
|
|
renderWithSimilarSurface ContentColorAlpha (ceiling (fromIntegral w*s)) (ceiling (fromIntegral h*s)) $ \surface' -> do
|
2011-07-17 20:06:33 +02:00
|
|
|
renderWith surface' $ do
|
|
|
|
scale 0.5 0.5
|
|
|
|
downscaled (2*s) surface
|
|
|
|
paint
|
|
|
|
withPatternForSurface surface' setSource
|
|
|
|
|
|
|
|
| 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
|
|
|
|
} deriving Show
|
|
|
|
|
2011-07-16 10:46:26 +02:00
|
|
|
data DesktopStyle = DesktopStyle { desktopFont :: !String
|
|
|
|
, desktopLabelWidth :: !Int
|
|
|
|
, desktopLabelGap :: !Int
|
|
|
|
, desktopColor :: !Color
|
|
|
|
, desktopBorder :: !BorderConfig
|
|
|
|
} deriving Show
|
|
|
|
|
2011-07-16 02:43:19 +02:00
|
|
|
data TaskbarConfig = TaskbarConfig { taskMaxSize :: !Int
|
|
|
|
, normalTaskStyle :: !TaskStyle
|
|
|
|
, activeTaskStyle :: !TaskStyle
|
2011-07-16 10:46:26 +02:00
|
|
|
, desktopStyle :: !(Maybe (DesktopStyle, DesktopStyle))
|
2011-07-15 09:17:57 +02:00
|
|
|
} deriving Show
|
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)
|
2011-07-16 10:46:26 +02:00
|
|
|
, 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) }}
|
2011-07-16 10:46:26 +02:00
|
|
|
, desktopStyle = Nothing
|
2011-07-15 09:17:57 +02:00
|
|
|
}
|
2011-07-14 22:50:03 +02:00
|
|
|
|
|
|
|
data Taskbar = Taskbar TaskbarConfig deriving Show
|
|
|
|
|
2011-07-15 15:31:46 +02:00
|
|
|
instance Show Surface where
|
|
|
|
show _ = "Surface <?>"
|
|
|
|
|
2011-07-18 00:59:40 +02:00
|
|
|
data TaskbarState = TaskbarState { taskbarActiveWindow :: !Window
|
|
|
|
, taskbarDesktopCount :: !Int
|
|
|
|
, taskbarCurrentDesktop :: !Int
|
|
|
|
, taskbarWindows :: ![Window]
|
|
|
|
, taskbarWindowStates :: !(M.Map Window WindowState)
|
|
|
|
, taskbarWindowIcons :: !(M.Map Window [(Int, Surface)])
|
|
|
|
, taskbarWindowScaledIcons :: !(M.Map Window (IORef (Maybe (Int, Surface))))
|
|
|
|
, taskbarWindowScreens :: !(M.Map Window Xlib.Rectangle)
|
2011-07-15 09:17:57 +02:00
|
|
|
} deriving Show
|
|
|
|
|
|
|
|
data WindowState = WindowState { windowTitle :: !String
|
|
|
|
, windowDesktop :: !Int
|
|
|
|
, windowVisible :: !Bool
|
|
|
|
} deriving (Show, Eq)
|
|
|
|
|
2011-07-18 00:59:40 +02:00
|
|
|
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)
|
2011-07-15 09:17:57 +02:00
|
|
|
| DesktopCountUpdate Int
|
2011-07-16 10:46:26 +02:00
|
|
|
| CurrentDesktopUpdate Int
|
2011-07-15 09:17:57 +02:00
|
|
|
| ActiveWindowUpdate Window
|
|
|
|
deriving (Show, Typeable)
|
2011-07-14 22:50:03 +02:00
|
|
|
|
2011-07-18 00:59:40 +02:00
|
|
|
instance Show (IORef a) where
|
|
|
|
show _ = "IORef <?>"
|
|
|
|
|
2011-07-14 22:50:03 +02:00
|
|
|
instance WidgetClass Taskbar where
|
|
|
|
type WidgetData Taskbar = TaskbarState
|
|
|
|
|
|
|
|
initWidget (Taskbar _) phi dispvar = do
|
2011-07-15 09:17:57 +02:00
|
|
|
forkIO $ taskbarRunner phi dispvar
|
|
|
|
|
2011-07-18 00:59:40 +02:00
|
|
|
return $ TaskbarState 0 0 (-1) [] M.empty M.empty M.empty M.empty
|
2011-07-14 22:50:03 +02:00
|
|
|
|
|
|
|
|
2011-07-17 19:20:19 +02:00
|
|
|
minSize _ _ _ = 0
|
2011-07-14 22:50:03 +02:00
|
|
|
weight _ = 1
|
|
|
|
|
2011-07-16 02:43:19 +02:00
|
|
|
render (Taskbar config) TaskbarState { taskbarActiveWindow = activeWindow
|
|
|
|
, taskbarDesktopCount = desktopCount
|
2011-07-16 10:46:26 +02:00
|
|
|
, taskbarCurrentDesktop = currentDesktop
|
2011-07-16 02:43:19 +02:00
|
|
|
, taskbarWindows = windows
|
|
|
|
, taskbarWindowStates = windowStates
|
|
|
|
, taskbarWindowIcons = windowIcons
|
2011-07-18 00:59:40 +02:00
|
|
|
, taskbarWindowScaledIcons = windowScaledIcons
|
2011-07-16 15:55:31 +02:00
|
|
|
, taskbarWindowScreens = windowScreens
|
|
|
|
} w h screen = do
|
|
|
|
let screenWindows = filter ((== Just screen) . flip M.lookup windowScreens) windows
|
|
|
|
desktopNumbers = take desktopCount [0..]
|
|
|
|
desktops = map (\desktop -> (desktop, filter (fromMaybe False . fmap (windowOnDesktop desktop) . flip M.lookup windowStates) screenWindows)) desktopNumbers
|
2011-07-16 10:46:26 +02:00
|
|
|
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
|
2011-07-16 15:55:31 +02:00
|
|
|
desktopsWidth = sum $ map dwidth desktopNumbers
|
|
|
|
windowWidth = if windowCount == 0 then 0 else min (taskMaxSize config) ((w - desktopsWidth) `div` windowCount)
|
|
|
|
|
|
|
|
flip (flip foldM_ 0) desktops $ \nwindows (desktop, desktopWindows) -> do
|
|
|
|
let dstyle' = dstyle desktop
|
|
|
|
dx = dleftwidth desktop + (sum $ map dwidth $ take desktop [0..]) + nwindows*windowWidth
|
|
|
|
|
|
|
|
case dstyle' of
|
|
|
|
Just ds -> do
|
|
|
|
let (r, g, b, a) = desktopColor ds
|
|
|
|
save
|
|
|
|
drawBorder (desktopBorder ds) (dx - dleftwidth desktop) 0 (dwidth desktop + windowWidth * length desktopWindows) h
|
|
|
|
clip
|
|
|
|
|
|
|
|
setSourceRGBA r g b a
|
|
|
|
renderText (desktopFont ds) (fromIntegral (dx - dlabelwidth desktop - gap desktop ds)) 0 (dlabelwidth desktop) h $ show (desktop+1)
|
|
|
|
|
|
|
|
restore
|
|
|
|
_ -> return ()
|
2011-07-15 09:17:57 +02:00
|
|
|
|
2011-07-16 15:55:31 +02:00
|
|
|
forM_ (zip [0..] desktopWindows) $ \(i, window) -> do
|
|
|
|
let style = (if window == activeWindow then activeTaskStyle else normalTaskStyle) config
|
|
|
|
(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)
|
|
|
|
mstate = M.lookup window windowStates
|
|
|
|
micons = M.lookup window windowIcons
|
2011-07-18 00:59:40 +02:00
|
|
|
mscaledIconRef = M.lookup window windowScaledIcons
|
2011-07-16 15:55:31 +02:00
|
|
|
x = dx + i*windowWidth
|
2011-07-16 10:46:26 +02:00
|
|
|
|
2011-07-18 00:59:40 +02:00
|
|
|
case (mstate, micons, mscaledIconRef) of
|
|
|
|
(Just state, Just icons, Just scaledIconRef) -> do
|
2011-07-15 15:31:46 +02:00
|
|
|
save
|
2011-07-16 15:55:31 +02:00
|
|
|
drawBorder (taskBorder style) x 0 windowWidth h
|
2011-07-15 15:31:46 +02:00
|
|
|
clip
|
|
|
|
|
2011-07-16 02:43:19 +02:00
|
|
|
setSourceRGBA r g b a
|
2011-07-16 15:55:31 +02:00
|
|
|
renderText (taskFont style) (fromIntegral (x + leftBorder + h' + 3)) 0 (windowWidth - leftBorder - h' - 3 - rightBorder) h $ windowTitle state
|
2011-07-15 15:31:46 +02:00
|
|
|
|
|
|
|
restore
|
2011-07-16 10:46:26 +02:00
|
|
|
|
2011-07-18 00:59:40 +02:00
|
|
|
mscaledIcon <- liftIO $ readIORef scaledIconRef
|
|
|
|
scaledIcon <- case mscaledIcon of
|
|
|
|
Just (size, icon) | size == h' -> do
|
|
|
|
return $ Just icon
|
|
|
|
_ -> do
|
|
|
|
case bestIcon icons of
|
|
|
|
Just icon -> do
|
|
|
|
scaledIcon <- liftIO $ createSimilarSurface icon ContentColorAlpha h' h'
|
|
|
|
renderWith scaledIcon $ do
|
|
|
|
imageW <- imageSurfaceGetWidth icon
|
|
|
|
imageH <- imageSurfaceGetHeight icon
|
|
|
|
|
|
|
|
let scalef = (fromIntegral h')/(fromIntegral $ max imageW imageH)
|
|
|
|
|
|
|
|
case True of
|
|
|
|
_ | imageH < imageW -> translate 0 (fromIntegral (imageW-imageH)*scalef/2)
|
|
|
|
| otherwise -> translate (fromIntegral (imageH-imageW)*scalef/2) 0
|
|
|
|
|
|
|
|
downscaled scalef icon
|
|
|
|
paint
|
|
|
|
liftIO $ writeIORef scaledIconRef $ Just (h', scaledIcon)
|
|
|
|
return $ Just scaledIcon
|
|
|
|
|
|
|
|
Nothing -> return Nothing
|
|
|
|
|
|
|
|
case scaledIcon of
|
2011-07-16 15:55:31 +02:00
|
|
|
Just icon -> do
|
|
|
|
save
|
|
|
|
translate (fromIntegral $ x + leftBorder) (fromIntegral $ borderTop $ margin $ taskBorder style)
|
2011-07-18 00:59:40 +02:00
|
|
|
taskIconStyle style icon
|
2011-07-16 15:55:31 +02:00
|
|
|
paint
|
|
|
|
restore
|
|
|
|
|
2011-07-18 00:59:40 +02:00
|
|
|
Nothing ->
|
|
|
|
return ()
|
2011-07-16 15:55:31 +02:00
|
|
|
|
|
|
|
_ -> return ()
|
|
|
|
|
|
|
|
return $ nwindows + length desktopWindows
|
2011-07-16 10:46:26 +02:00
|
|
|
|
2011-07-15 09:17:57 +02:00
|
|
|
|
|
|
|
handleMessage _ priv m = case (fromMessage m) of
|
2011-07-18 00:59:40 +02:00
|
|
|
Just (WindowListUpdate windows windowStates icons scaledIcons screens) -> priv {taskbarWindows = windows
|
|
|
|
, taskbarWindowStates = windowStates
|
|
|
|
, taskbarWindowIcons = icons
|
|
|
|
, taskbarWindowScaledIcons = scaledIcons
|
|
|
|
, taskbarWindowScreens = screens
|
|
|
|
}
|
2011-07-15 09:17:57 +02:00
|
|
|
Just (DesktopCountUpdate count) -> priv {taskbarDesktopCount = count}
|
2011-07-16 10:46:26 +02:00
|
|
|
Just (CurrentDesktopUpdate current) -> priv {taskbarCurrentDesktop = current}
|
2011-07-15 09:17:57 +02:00
|
|
|
Just (ActiveWindowUpdate window) -> priv {taskbarActiveWindow = window}
|
|
|
|
_ -> priv
|
|
|
|
|
|
|
|
|
2011-07-16 10:46:26 +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
|
2011-07-16 10:46:26 +02:00
|
|
|
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-07-18 00:59:40 +02:00
|
|
|
bestIcon :: [(Int, Surface)] -> Maybe Surface
|
|
|
|
bestIcon icons = fmap snd . listToMaybe $ sortBy compareIcons icons
|
2011-07-16 01:28:47 +02:00
|
|
|
where
|
|
|
|
compareIcons = flip (compare `on` fst)
|
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
|
2011-07-16 15:55:31 +02:00
|
|
|
let screens = getScreens dispvar
|
2011-07-18 00:59:40 +02:00
|
|
|
(windows, states, icons, scaledIcons, windowScreens) <- liftIO $ withDisplay dispvar $ \disp -> do
|
2011-07-18 12:44:55 +02:00
|
|
|
(windows, states, icons, scaledIcons, windowScreens) <- getWindowStates disp screens (getAtoms dispvar) M.empty M.empty M.empty M.empty
|
2011-07-15 09:17:57 +02:00
|
|
|
desktopCount <- getDesktopCount disp (getAtoms dispvar)
|
2011-07-16 10:46:26 +02:00
|
|
|
current <- getCurrentDesktop disp (getAtoms dispvar)
|
2011-07-15 09:17:57 +02:00
|
|
|
activeWindow <- getActiveWindow disp (getAtoms dispvar)
|
2011-07-18 00:59:40 +02:00
|
|
|
sendMessage phi $ WindowListUpdate windows states icons scaledIcons windowScreens
|
2011-07-15 09:17:57 +02:00
|
|
|
sendMessage phi $ DesktopCountUpdate desktopCount
|
2011-07-16 10:46:26 +02:00
|
|
|
sendMessage phi $ CurrentDesktopUpdate current
|
2011-07-15 09:17:57 +02:00
|
|
|
sendMessage phi $ ActiveWindowUpdate activeWindow
|
2011-07-18 00:59:40 +02:00
|
|
|
return (windows, states, icons, scaledIcons, windowScreens)
|
2011-07-15 09:17:57 +02:00
|
|
|
sendMessage phi Repaint
|
|
|
|
|
2011-07-18 00:59:40 +02:00
|
|
|
flip evalStateT (windows, states, icons, scaledIcons, windowScreens) $ forever $ do
|
2011-07-15 09:17:57 +02:00
|
|
|
m <- receiveMessage phi
|
|
|
|
case (fromMessage m) of
|
2011-07-16 15:55:31 +02:00
|
|
|
Just event ->
|
|
|
|
handleEvent phi dispvar event
|
2011-07-15 09:17:57 +02:00
|
|
|
_ ->
|
|
|
|
return ()
|
2011-07-15 15:31:46 +02:00
|
|
|
|
2011-07-18 00:59:40 +02:00
|
|
|
handleEvent :: Phi -> Display -> XExtras.Event -> StateT ([Window], M.Map Window WindowState, M.Map Window [(Int, Surface)], M.Map Window (IORef (Maybe (Int, Surface))), M.Map Window Xlib.Rectangle) IO ()
|
2011-07-16 15:55:31 +02:00
|
|
|
handleEvent phi dispvar XExtras.PropertyEvent {XExtras.ev_atom = atom, XExtras.ev_window = window} = do
|
2011-07-15 09:17:57 +02:00
|
|
|
let atoms = getAtoms dispvar
|
2011-07-16 15:55:31 +02:00
|
|
|
let screens = getScreens dispvar
|
2011-07-15 09:17:57 +02:00
|
|
|
|
2011-07-17 19:20:19 +02:00
|
|
|
when (elem atom $ Xlib.wM_NAME : map ($ atoms) [ atom_NET_ACTIVE_WINDOW
|
|
|
|
, atom_NET_NUMBER_OF_DESKTOPS
|
|
|
|
, atom_NET_CURRENT_DESKTOP
|
|
|
|
, atom_NET_CLIENT_LIST
|
|
|
|
, atom_NET_WM_ICON
|
|
|
|
, atom_NET_WM_NAME
|
|
|
|
, atom_NET_WM_DESKTOP
|
|
|
|
, atom_NET_WM_STATE
|
2011-07-15 09:17:57 +02:00
|
|
|
]) $ withDisplay dispvar $ \disp -> do
|
|
|
|
let rootwin = Xlib.defaultRootWindow disp
|
|
|
|
if (window == rootwin)
|
|
|
|
then do
|
|
|
|
when (atom == atom_NET_ACTIVE_WINDOW atoms) $ do
|
|
|
|
activeWindow <- liftIO $ getActiveWindow disp atoms
|
|
|
|
sendMessage phi $ ActiveWindowUpdate activeWindow
|
|
|
|
sendMessage phi Repaint
|
|
|
|
when (atom == atom_NET_NUMBER_OF_DESKTOPS atoms) $ do
|
|
|
|
desktopCount <- liftIO $ getDesktopCount disp atoms
|
|
|
|
sendMessage phi $ DesktopCountUpdate desktopCount
|
|
|
|
sendMessage phi Repaint
|
2011-07-16 10:46:26 +02:00
|
|
|
when (atom == atom_NET_CURRENT_DESKTOP atoms) $ do
|
|
|
|
current <- liftIO $ getCurrentDesktop disp atoms
|
|
|
|
sendMessage phi $ CurrentDesktopUpdate current
|
|
|
|
sendMessage phi Repaint
|
2011-07-15 09:17:57 +02:00
|
|
|
when (atom == atom_NET_CLIENT_LIST atoms) $ do
|
2011-07-18 00:59:40 +02:00
|
|
|
(windows, windowStates, icons, scaledIcons, windowScreens) <- get
|
2011-07-18 12:44:55 +02:00
|
|
|
(windows', windowStates', icons', scaledIcons', windowScreens') <- liftIO $ getWindowStates disp screens atoms windowStates icons scaledIcons windowScreens
|
2011-07-15 09:17:57 +02:00
|
|
|
|
2011-07-15 15:31:46 +02:00
|
|
|
when (windows /= windows') $ do
|
2011-07-18 00:59:40 +02:00
|
|
|
sendMessage phi $ WindowListUpdate windows' windowStates' icons' scaledIcons' windowScreens'
|
2011-07-15 09:17:57 +02:00
|
|
|
sendMessage phi Repaint
|
2011-07-18 00:59:40 +02:00
|
|
|
put (windows', windowStates', icons', scaledIcons', windowScreens')
|
2011-07-15 09:17:57 +02:00
|
|
|
|
|
|
|
else do
|
2011-07-18 00:59:40 +02:00
|
|
|
(windows, windowStates, icons, scaledIcons, windowScreens) <- get
|
2011-07-15 09:17:57 +02:00
|
|
|
when (elem window windows) $ do
|
2011-07-15 15:31:46 +02:00
|
|
|
when (atom == atom_NET_WM_ICON atoms) $ do
|
|
|
|
icon <- liftIO $ getWindowIcons disp atoms window
|
2011-07-18 00:59:40 +02:00
|
|
|
scaledIcon <- liftIO $ newIORef Nothing
|
2011-07-15 15:31:46 +02:00
|
|
|
let icons' = M.insert window icon icons
|
2011-07-18 00:59:40 +02:00
|
|
|
scaledIcons' = M.insert window scaledIcon scaledIcons
|
|
|
|
sendMessage phi $ WindowListUpdate windows windowStates icons' scaledIcons' windowScreens
|
2011-07-15 09:17:57 +02:00
|
|
|
sendMessage phi Repaint
|
2011-07-18 00:59:40 +02:00
|
|
|
put (windows, windowStates, icons', scaledIcons', windowScreens)
|
2011-07-15 15:31:46 +02:00
|
|
|
|
|
|
|
when (atom /= atom_NET_WM_ICON atoms) $ do
|
|
|
|
let windowState = M.lookup window windowStates
|
|
|
|
windowState' <- liftIO $ getWindowState disp atoms window
|
|
|
|
|
|
|
|
when (windowState /= (Just windowState')) $ do
|
|
|
|
let windowStates' = M.insert window windowState' windowStates
|
2011-07-18 00:59:40 +02:00
|
|
|
sendMessage phi $ WindowListUpdate windows windowStates' icons scaledIcons windowScreens
|
2011-07-15 15:31:46 +02:00
|
|
|
sendMessage phi Repaint
|
2011-07-18 00:59:40 +02:00
|
|
|
put (windows, windowStates', icons, scaledIcons, windowScreens)
|
2011-07-16 15:55:31 +02:00
|
|
|
|
|
|
|
handleEvent phi dispvar XExtras.ConfigureEvent {XExtras.ev_window = window} = do
|
|
|
|
let screens = getScreens dispvar
|
|
|
|
|
2011-07-18 00:59:40 +02:00
|
|
|
(windows, windowStates, icons, scaledIcons, windowScreens) <- get
|
2011-07-16 15:55:31 +02:00
|
|
|
when (elem window windows) $ withDisplay dispvar $ \disp -> do
|
|
|
|
let screen = M.lookup window windowScreens
|
|
|
|
screen' <- liftIO $ getWindowScreen disp screens window
|
|
|
|
when (screen /= (Just screen')) $ do
|
|
|
|
let windowScreens' = M.insert window screen' windowScreens
|
2011-07-18 00:59:40 +02:00
|
|
|
sendMessage phi $ WindowListUpdate windows windowStates icons scaledIcons windowScreens'
|
2011-07-16 15:55:31 +02:00
|
|
|
sendMessage phi Repaint
|
2011-07-18 00:59:40 +02:00
|
|
|
put (windows, windowStates, icons, scaledIcons, windowScreens')
|
2011-07-16 15:55:31 +02:00
|
|
|
|
|
|
|
handleEvent _ _ _ = return ()
|
|
|
|
|
2011-07-15 09:17:57 +02:00
|
|
|
|
|
|
|
getDesktopCount :: Xlib.Display -> Atoms -> IO Int
|
|
|
|
getDesktopCount disp atoms =
|
|
|
|
liftM (fromIntegral . fromMaybe 0 . join . fmap listToMaybe) $ XExtras.getWindowProperty32 disp (atom_NET_NUMBER_OF_DESKTOPS atoms) $ Xlib.defaultRootWindow disp
|
|
|
|
|
2011-07-16 15:55:31 +02:00
|
|
|
|
2011-07-16 10:46:26 +02:00
|
|
|
getCurrentDesktop :: Xlib.Display -> Atoms -> IO Int
|
|
|
|
getCurrentDesktop disp atoms =
|
|
|
|
liftM (fromIntegral . fromMaybe (-1) . join . fmap listToMaybe) $ XExtras.getWindowProperty32 disp (atom_NET_CURRENT_DESKTOP atoms) $ Xlib.defaultRootWindow disp
|
|
|
|
|
2011-07-15 09:17:57 +02:00
|
|
|
getActiveWindow :: Xlib.Display -> Atoms -> IO Window
|
|
|
|
getActiveWindow disp atoms =
|
|
|
|
liftM (fromIntegral . fromMaybe 0 . join . fmap listToMaybe) $ XExtras.getWindowProperty32 disp (atom_NET_ACTIVE_WINDOW atoms) $ Xlib.defaultRootWindow disp
|
|
|
|
|
2011-07-18 12:44:55 +02:00
|
|
|
getWindowStates :: Xlib.Display -> [Xlib.Rectangle] -> Atoms -> M.Map Window WindowState -> M.Map Window [(Int, Surface)] -> M.Map Window (IORef (Maybe (Int, Surface))) -> M.Map Window Xlib.Rectangle
|
2011-07-18 00:59:40 +02:00
|
|
|
-> IO ([Window], M.Map Window WindowState, M.Map Window [(Int, Surface)], M.Map Window (IORef (Maybe (Int, Surface))), M.Map Window Xlib.Rectangle)
|
2011-07-18 12:44:55 +02:00
|
|
|
getWindowStates disp screens atoms windowStates windowIcons windowScaledIcons windowScreens = do
|
|
|
|
windows <- getWindowList disp atoms
|
2011-07-15 09:17:57 +02:00
|
|
|
|
|
|
|
let windowStates' = map (\w -> (w, M.lookup w windowStates)) windows
|
2011-07-15 15:31:46 +02:00
|
|
|
windowIcons' = map (\w -> (w, M.lookup w windowIcons)) windows
|
2011-07-18 00:59:40 +02:00
|
|
|
windowScaledIcons' = map (\w -> (w, M.lookup w windowScaledIcons)) windows
|
2011-07-16 15:55:31 +02:00
|
|
|
windowScreens' = map (\w -> (w, M.lookup w windowScreens)) windows
|
2011-07-15 09:17:57 +02:00
|
|
|
|
|
|
|
newWindowStates <- mapM getWindowState' windowStates'
|
2011-07-15 15:31:46 +02:00
|
|
|
newWindowIcons <- mapM getWindowIcons' windowIcons'
|
2011-07-18 00:59:40 +02:00
|
|
|
newWindowScaledIcons <- mapM getScaledIcons windowScaledIcons'
|
2011-07-16 15:55:31 +02:00
|
|
|
newWindowScreens <- mapM getWindowScreen' windowScreens'
|
2011-07-15 09:17:57 +02:00
|
|
|
|
2011-07-18 00:59:40 +02:00
|
|
|
return (windows, M.fromList newWindowStates, M.fromList newWindowIcons, M.fromList newWindowScaledIcons, M.fromList newWindowScreens)
|
2011-07-15 09:17:57 +02:00
|
|
|
where
|
|
|
|
getWindowState' (window, Just windowState) = return (window, windowState)
|
|
|
|
getWindowState' (window, Nothing) = do
|
2011-07-16 15:55:31 +02:00
|
|
|
Xlib.selectInput disp window $ Xlib.propertyChangeMask .|. Xlib.structureNotifyMask
|
2011-07-15 09:17:57 +02:00
|
|
|
windowState <- getWindowState disp atoms window
|
|
|
|
return (window, windowState)
|
2011-07-15 15:31:46 +02:00
|
|
|
|
|
|
|
getWindowIcons' (window, Just icons) = return (window, icons)
|
|
|
|
getWindowIcons' (window, Nothing) = do
|
|
|
|
icons <- getWindowIcons disp atoms window
|
|
|
|
return (window, icons)
|
2011-07-16 15:55:31 +02:00
|
|
|
|
2011-07-18 00:59:40 +02:00
|
|
|
getScaledIcons (window, Just icon) = return (window, icon)
|
|
|
|
getScaledIcons (window, Nothing) = liftM2 (,) (return window) $ newIORef Nothing
|
|
|
|
|
2011-07-16 15:55:31 +02:00
|
|
|
getWindowScreen' (window, Just screen) = return (window, screen)
|
|
|
|
getWindowScreen' (window, Nothing) = do
|
|
|
|
screen <- getWindowScreen disp screens window
|
|
|
|
return (window, screen)
|
|
|
|
|
2011-07-15 09:17:57 +02:00
|
|
|
|
2011-07-15 15:31:46 +02:00
|
|
|
getWindowState :: Xlib.Display -> Atoms -> Window -> IO WindowState
|
2011-07-15 09:17:57 +02:00
|
|
|
getWindowState disp atoms window = do
|
|
|
|
netwmname <- liftM (fmap (decode . map fromIntegral)) $ XExtras.getWindowProperty8 disp (atom_NET_WM_NAME atoms) window
|
|
|
|
wmname <- case netwmname of
|
|
|
|
Just name -> return name
|
2011-07-17 19:20:19 +02:00
|
|
|
Nothing -> liftM (map unsignedChr . fromMaybe []) $ XExtras.getWindowProperty8 disp Xlib.wM_NAME window
|
2011-07-15 09:17:57 +02:00
|
|
|
|
|
|
|
workspace <- liftM (fromIntegral . fromMaybe 0xFFFFFFFF . join . fmap listToMaybe) $ XExtras.getWindowProperty32 disp (atom_NET_WM_DESKTOP atoms) window
|
|
|
|
|
|
|
|
visible <- showWindow disp atoms window
|
|
|
|
|
|
|
|
return $ WindowState wmname workspace visible
|
|
|
|
where
|
|
|
|
unsignedChr = chr . fromIntegral . (fromIntegral :: (CChar -> CUChar))
|
|
|
|
|
2011-07-16 01:28:47 +02:00
|
|
|
getWindowIcons :: Xlib.Display -> Atoms -> Window -> IO [(Int, Surface)]
|
2011-07-15 15:31:46 +02:00
|
|
|
getWindowIcons disp atoms window = XExtras.getWindowProperty32 disp (atom_NET_WM_ICON atoms) window >>= readIcons . fromMaybe []
|
|
|
|
|
2011-07-16 15:55:31 +02:00
|
|
|
|
2011-07-16 01:28:47 +02:00
|
|
|
readIcons :: [CLong] -> IO [(Int, Surface)]
|
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
|
|
|
|
icon <- createImageSurface FormatARGB32 (fromIntegral width) (fromIntegral height)
|
|
|
|
surfaceData <- imageSurfaceGetPixels icon :: 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 icon
|
|
|
|
|
|
|
|
moreIcons <- readIcons rest
|
2011-07-16 01:28:47 +02:00
|
|
|
return $ (fromIntegral $ max width height, icon):moreIcons
|
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
|
|
|
|
|
|
|
getWindowScreen :: Xlib.Display -> [Xlib.Rectangle] -> Window -> IO Xlib.Rectangle
|
|
|
|
getWindowScreen disp screens window = do
|
|
|
|
(_, _, _, width, height, _, _) <- Xlib.getGeometry disp window
|
|
|
|
(ret, x, y, _) <- Xlib.translateCoordinates disp window (Xlib.defaultRootWindow disp) 0 0
|
|
|
|
|
|
|
|
case ret of
|
|
|
|
True -> do
|
|
|
|
let windowRect = Xlib.Rectangle x y width height
|
|
|
|
screen = maximumBy (compare `on` unionArea windowRect) screens
|
|
|
|
return screen
|
|
|
|
False ->
|
|
|
|
return $ head screens
|
|
|
|
|
|
|
|
|
2011-07-15 09:17:57 +02:00
|
|
|
showWindow :: Xlib.Display -> Atoms -> Window -> IO Bool
|
|
|
|
showWindow disp atoms window = do
|
|
|
|
states <- liftM (map fromIntegral . fromMaybe []) $ XExtras.getWindowProperty32 disp (atom_NET_WM_STATE atoms) window
|
|
|
|
transientForHint <- XExtras.getTransientForHint disp window
|
|
|
|
windowType <- liftM (fromMaybe (atom_NET_WM_WINDOW_TYPE_NORMAL atoms) . fmap fromIntegral . join . fmap listToMaybe) $ XExtras.getWindowProperty32 disp (atom_NET_WM_STATE atoms) window
|
|
|
|
|
|
|
|
return $ not $ or [ elem (atom_NET_WM_STATE_SKIP_TASKBAR atoms) states
|
|
|
|
, transientForHint /= Nothing
|
|
|
|
, 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-07-18 12:44:55 +02:00
|
|
|
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
|
2011-07-14 22:50:03 +02:00
|
|
|
|
|
|
|
taskbar :: TaskbarConfig -> Widget
|
|
|
|
taskbar config = do
|
|
|
|
Widget $ Taskbar config
|