For now, print desktop names instead of numbers

This commit is contained in:
Matthias Schiffer 2011-09-06 12:54:58 +02:00
parent 499eaf95fb
commit 42d5f27d32
3 changed files with 31 additions and 10 deletions

View file

@ -141,6 +141,7 @@ data TaskbarState = TaskbarState { taskbarScreens :: ![Xlib.Rectangle]
, taskbarActiveWindow :: !Window , taskbarActiveWindow :: !Window
, taskbarDesktopCount :: !Int , taskbarDesktopCount :: !Int
, taskbarCurrentDesktop :: !Int , taskbarCurrentDesktop :: !Int
, taskbarDesktopNames :: ![String]
, taskbarWindows :: ![Window] , taskbarWindows :: ![Window]
, taskbarWindowStates :: !(M.Map Window WindowState) , taskbarWindowStates :: !(M.Map Window WindowState)
} deriving Eq } deriving Eq
@ -202,6 +203,7 @@ cached t = liftT t . liftIOStateT . runIOCache
data TaskbarMessage = WindowListUpdate ![Xlib.Window] !(M.Map Window WindowState) data TaskbarMessage = WindowListUpdate ![Xlib.Window] !(M.Map Window WindowState)
| DesktopCountUpdate !Int | DesktopCountUpdate !Int
| CurrentDesktopUpdate !Int | CurrentDesktopUpdate !Int
| DesktopNamesUpdate ![String]
| ActiveWindowUpdate !Window | ActiveWindowUpdate !Window
deriving (Typeable, Show) deriving (Typeable, Show)
@ -210,7 +212,7 @@ instance Widget Taskbar TaskbarState (M.Map Window WindowCache) where
phi' <- dupPhi phi phi' <- dupPhi phi
forkIO $ taskbarRunner phi' dispvar forkIO $ taskbarRunner phi' dispvar
return $ TaskbarState (map fst screens) 0 0 (-1) [] M.empty return $ TaskbarState (map fst screens) 0 0 (-1) [] [] M.empty
initCache _ = M.empty initCache _ = M.empty
@ -221,13 +223,14 @@ instance Widget Taskbar TaskbarState (M.Map Window WindowCache) where
, taskbarActiveWindow = activeWindow , taskbarActiveWindow = activeWindow
, taskbarDesktopCount = desktopCount , taskbarDesktopCount = desktopCount
, taskbarCurrentDesktop = currentDesktop , taskbarCurrentDesktop = currentDesktop
, taskbarDesktopNames = desktopNames
, taskbarWindows = windows , taskbarWindows = windows
, taskbarWindowStates = windowStates , taskbarWindowStates = windowStates
} _ _ w h screen = do } _ _ w h screen = do
let windowScreen w = maximumBy (compare `on` unionArea (windowGeometry w)) screens let windowScreen w = maximumBy (compare `on` unionArea (windowGeometry w)) screens
screenWindows = filter ((== Just screen) . fmap windowScreen . flip M.lookup windowStates) windows screenWindows = filter ((== Just screen) . fmap windowScreen . flip M.lookup windowStates) windows
desktopNumbers = take desktopCount [0..] desktopNumbers = take desktopCount $ zip [0..] (desktopNames ++ repeat "")
desktops = map (\desktop -> (desktop, filter (fromMaybe False . fmap (windowOnDesktop desktop) . flip M.lookup windowStates) screenWindows)) desktopNumbers desktops = map (\desktop -> (desktop, filter (fromMaybe False . fmap (windowOnDesktop . fst $ desktop) . flip M.lookup windowStates) screenWindows)) desktopNumbers
windowCount = sum $ map (length . snd) $ desktops windowCount = sum $ map (length . snd) $ desktops
@ -241,7 +244,7 @@ instance Widget Taskbar TaskbarState (M.Map Window WindowCache) where
-> (borderH $ margin border) + 2*(borderWidth border) + (borderH $ padding border) -> (borderH $ margin border) + 2*(borderWidth border) + (borderH $ padding border)
+ dlabelwidth d + gap d ds) $ dstyle d + dlabelwidth d + gap d ds) $ dstyle d
desktopsWidth = sum $ map dwidth desktopNumbers desktopsWidth = sum $ map (dwidth . fst) desktopNumbers
windowWidth = if windowCount == 0 then 0 else min (taskMaxSize config) ((w - desktopsWidth) `div` windowCount) windowWidth = if windowCount == 0 then 0 else min (taskMaxSize config) ((w - desktopsWidth) `div` windowCount)
surface <- liftIO $ createImageSurface FormatARGB32 w h surface <- liftIO $ createImageSurface FormatARGB32 w h
@ -254,19 +257,19 @@ instance Widget Taskbar TaskbarState (M.Map Window WindowCache) where
setOperator OperatorOver setOperator OperatorOver
flip (flip foldM_ 0) desktops $ \nwindows (desktop, desktopWindows) -> do flip (flip foldM_ 0) desktops $ \nwindows (desktop, desktopWindows) -> do
let dstyle' = dstyle desktop let dstyle' = dstyle (fst desktop)
dx = dleftwidth desktop + (sum $ map dwidth $ take desktop [0..]) + nwindows*windowWidth dx = dleftwidth (fst desktop) + (sum $ map dwidth $ take (fst desktop) [0..]) + nwindows*windowWidth
case dstyle' of case dstyle' of
Just ds -> do Just ds -> do
let (r, g, b, a) = desktopColor ds let (r, g, b, a) = desktopColor ds
lift $ do lift $ do
save save
drawBorder (desktopBorder ds) (dx - dleftwidth desktop) 0 (dwidth desktop + windowWidth * length desktopWindows) h drawBorder (desktopBorder ds) (dx - dleftwidth (fst desktop)) 0 (dwidth (fst desktop) + windowWidth * length desktopWindows) h
clip clip
setSourceRGBA r g b a setSourceRGBA r g b a
renderText (desktopFont ds) (fromIntegral (dx - dlabelwidth desktop - gap desktop ds)) 0 (dlabelwidth desktop) h $ show (desktop+1) renderText (desktopFont ds) (fromIntegral (dx - dlabelwidth (fst desktop) - gap (fst desktop) ds)) 0 (dlabelwidth (fst desktop)) h $ snd desktop
restore restore
@ -303,6 +306,7 @@ instance Widget Taskbar TaskbarState (M.Map Window WindowCache) where
} }
Just (DesktopCountUpdate count) -> priv {taskbarDesktopCount = count} Just (DesktopCountUpdate count) -> priv {taskbarDesktopCount = count}
Just (CurrentDesktopUpdate current) -> priv {taskbarCurrentDesktop = current} Just (CurrentDesktopUpdate current) -> priv {taskbarCurrentDesktop = current}
Just (DesktopNamesUpdate names) -> priv {taskbarDesktopNames = names}
Just (ActiveWindowUpdate window) -> priv {taskbarActiveWindow = window} Just (ActiveWindowUpdate window) -> priv {taskbarActiveWindow = window}
_ -> case (fromMessage m) of _ -> case (fromMessage m) of
Just (UpdateScreens screens) -> priv {taskbarScreens = map fst screens} Just (UpdateScreens screens) -> priv {taskbarScreens = map fst screens}
@ -399,10 +403,12 @@ taskbarRunner phi dispvar = do
(windows, states) <- getWindowStates disp (getAtoms dispvar) M.empty (windows, states) <- getWindowStates disp (getAtoms dispvar) M.empty
desktopCount <- getDesktopCount disp (getAtoms dispvar) desktopCount <- getDesktopCount disp (getAtoms dispvar)
current <- getCurrentDesktop disp (getAtoms dispvar) current <- getCurrentDesktop disp (getAtoms dispvar)
names <- getDesktopNames disp (getAtoms dispvar)
activeWindow <- getActiveWindow disp (getAtoms dispvar) activeWindow <- getActiveWindow disp (getAtoms dispvar)
sendMessage phi $ WindowListUpdate windows states sendMessage phi $ WindowListUpdate windows states
sendMessage phi $ DesktopCountUpdate desktopCount sendMessage phi $ DesktopCountUpdate desktopCount
sendMessage phi $ CurrentDesktopUpdate current sendMessage phi $ CurrentDesktopUpdate current
sendMessage phi $ DesktopNamesUpdate names
sendMessage phi $ ActiveWindowUpdate activeWindow sendMessage phi $ ActiveWindowUpdate activeWindow
return (windows, states) return (windows, states)
sendMessage phi Repaint sendMessage phi Repaint
@ -422,6 +428,7 @@ handleEvent phi dispvar XExtras.PropertyEvent {XExtras.ev_atom = atom, XExtras.e
when (elem atom $ Xlib.wM_NAME : map ($ atoms) [ atom_NET_ACTIVE_WINDOW when (elem atom $ Xlib.wM_NAME : map ($ atoms) [ atom_NET_ACTIVE_WINDOW
, atom_NET_NUMBER_OF_DESKTOPS , atom_NET_NUMBER_OF_DESKTOPS
, atom_NET_CURRENT_DESKTOP , atom_NET_CURRENT_DESKTOP
, atom_NET_DESKTOP_NAMES
, atom_NET_CLIENT_LIST , atom_NET_CLIENT_LIST
, atom_NET_WM_ICON , atom_NET_WM_ICON
, atom_NET_WM_NAME , atom_NET_WM_NAME
@ -443,6 +450,10 @@ handleEvent phi dispvar XExtras.PropertyEvent {XExtras.ev_atom = atom, XExtras.e
current <- liftIO $ getCurrentDesktop disp atoms current <- liftIO $ getCurrentDesktop disp atoms
sendMessage phi $ CurrentDesktopUpdate current sendMessage phi $ CurrentDesktopUpdate current
sendMessage phi Repaint sendMessage phi Repaint
when (atom == atom_NET_DESKTOP_NAMES atoms) $ do
names <- liftIO $ getDesktopNames disp atoms
sendMessage phi $ DesktopNamesUpdate names
sendMessage phi Repaint
when (atom == atom_NET_CLIENT_LIST atoms) $ do when (atom == atom_NET_CLIENT_LIST atoms) $ do
(windows, windowStates) <- get (windows, windowStates) <- get
(windows', windowStates') <- liftIO $ getWindowStates disp atoms windowStates (windows', windowStates') <- liftIO $ getWindowStates disp atoms windowStates
@ -496,11 +507,19 @@ getDesktopCount :: Xlib.Display -> Atoms -> IO Int
getDesktopCount disp atoms = getDesktopCount disp atoms =
liftM (fromIntegral . fromMaybe 0 . join . fmap listToMaybe) $ XExtras.getWindowProperty32 disp (atom_NET_NUMBER_OF_DESKTOPS atoms) $ Xlib.defaultRootWindow disp liftM (fromIntegral . fromMaybe 0 . join . fmap listToMaybe) $ XExtras.getWindowProperty32 disp (atom_NET_NUMBER_OF_DESKTOPS atoms) $ Xlib.defaultRootWindow disp
getCurrentDesktop :: Xlib.Display -> Atoms -> IO Int getCurrentDesktop :: Xlib.Display -> Atoms -> IO Int
getCurrentDesktop disp atoms = getCurrentDesktop disp atoms =
liftM (fromIntegral . fromMaybe (-1) . join . fmap listToMaybe) $ XExtras.getWindowProperty32 disp (atom_NET_CURRENT_DESKTOP atoms) $ Xlib.defaultRootWindow disp liftM (fromIntegral . fromMaybe (-1) . join . fmap listToMaybe) $ XExtras.getWindowProperty32 disp (atom_NET_CURRENT_DESKTOP atoms) $ Xlib.defaultRootWindow disp
getDesktopNames :: Xlib.Display -> Atoms -> IO [String]
getDesktopNames disp atoms =
liftM (map (decode . map fromIntegral) . break' . fromMaybe []) $ XExtras.getWindowProperty8 disp (atom_NET_DESKTOP_NAMES atoms) $ Xlib.defaultRootWindow disp
where
break' l = case dropWhile (== 0) l of
[] -> []
l' -> w : break' l''
where (w, l'') = break (== 0) l'
getActiveWindow :: Xlib.Display -> Atoms -> IO Window getActiveWindow :: Xlib.Display -> Atoms -> IO Window
getActiveWindow disp atoms = getActiveWindow disp atoms =
liftM (fromIntegral . fromMaybe 0 . join . fmap listToMaybe) $ XExtras.getWindowProperty32 disp (atom_NET_ACTIVE_WINDOW atoms) $ Xlib.defaultRootWindow disp liftM (fromIntegral . fromMaybe 0 . join . fmap listToMaybe) $ XExtras.getWindowProperty32 disp (atom_NET_ACTIVE_WINDOW atoms) $ Xlib.defaultRootWindow disp

View file

@ -16,6 +16,7 @@ import Data.Maybe
import Data.Bits import Data.Bits
import Data.Char import Data.Char
import Control.Arrow ((&&&))
import Control.Concurrent import Control.Concurrent
import Control.Concurrent.MVar import Control.Concurrent.MVar
import Control.Monad.State.Strict import Control.Monad.State.Strict
@ -224,7 +225,7 @@ handleEvent disp ConfigureEvent { ev_window = window } | window == defaultRootWi
modify $ \state -> state { phiPanels = panels' } modify $ \state -> state { phiPanels = panels' }
sendMessage phi $ UpdateScreens $ map (\panel -> (panelScreenArea panel, panelWindow panel)) panels' sendMessage phi $ UpdateScreens $ map (panelScreenArea &&& panelWindow) panels'
sendMessage phi Repaint sendMessage phi Repaint
handleEvent _ _ = return () handleEvent _ _ = return ()

View file

@ -35,6 +35,7 @@ atoms = [ "UTF8_STRING"
, "_NET_ACTIVE_WINDOW" , "_NET_ACTIVE_WINDOW"
, "_NET_NUMBER_OF_DESKTOPS" , "_NET_NUMBER_OF_DESKTOPS"
, "_NET_CURRENT_DESKTOP" , "_NET_CURRENT_DESKTOP"
, "_NET_DESKTOP_NAMES"
, "_NET_CLIENT_LIST" , "_NET_CLIENT_LIST"
, "_MOTIF_WM_HINTS" , "_MOTIF_WM_HINTS"
, "_XEMBED" , "_XEMBED"