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/Systray.hs

293 lines
11 KiB
Haskell
Raw Normal View History

{-# LANGUAGE MultiParamTypeClasses, DeriveDataTypeable #-}
2011-07-17 19:20:19 +02:00
module Phi.Widgets.Systray ( systray
) where
import Control.Concurrent
import Control.Monad
2011-07-19 11:16:50 +02:00
import Control.Monad.State
import Control.Monad.Trans
2011-07-17 19:20:19 +02:00
2011-07-19 11:16:50 +02:00
import Data.Bits
import Data.IORef
2011-07-17 19:20:19 +02:00
import Data.Maybe
2011-07-19 11:16:50 +02:00
import Data.Typeable
import qualified Data.Map as M
2011-07-17 19:20:19 +02:00
import Foreign.C.Types
2011-08-11 18:53:02 +02:00
import Foreign.Marshal
import Foreign.Ptr
import Foreign.Storable
2011-07-17 19:20:19 +02:00
2011-07-19 11:16:50 +02:00
import Graphics.Rendering.Cairo
import Graphics.Rendering.Cairo.Types
2011-07-17 19:20:19 +02:00
import Graphics.X11.Xlib hiding (Display)
import qualified Graphics.X11.Xlib as Xlib
import Graphics.X11.Xlib.Extras
import Phi.Bindings.Util
2011-07-19 14:50:04 +02:00
import Phi.Bindings.SystrayErrorHandler
2011-07-17 19:20:19 +02:00
import Phi.Phi
import Phi.Types
import Phi.Widget
import Phi.X11.Atoms
2011-08-12 03:18:46 +02:00
data SystrayIconState = SystrayIconState !Window !Window deriving Show
2011-07-19 11:16:50 +02:00
data SystrayState = SystrayState !Phi !Rectangle !Int !(IORef Int) ![SystrayIconState]
instance Eq SystrayState where
_ == _ = False
2011-07-17 19:20:19 +02:00
data Systray = Systray deriving (Show, Eq)
2011-07-17 19:20:19 +02:00
2011-08-12 03:18:46 +02:00
data SystrayMessage = AddIcon !Window !Window | RemoveIcon !Window | RenderIcon !Window !Window !Int !Int !Int !Int !Bool
2011-07-19 11:16:50 +02:00
deriving (Show, Typeable)
2011-07-17 19:20:19 +02:00
instance Widget Systray SystrayState where
2011-07-17 19:20:19 +02:00
initWidget (Systray) phi dispvar = do
2011-08-12 02:11:09 +02:00
phi' <- dupPhi phi
forkIO $ systrayRunner phi' dispvar
2011-07-17 19:20:19 +02:00
2011-07-19 11:16:50 +02:00
lastReset <- newIORef 0
return $ SystrayState phi (head . getScreens $ dispvar) 0 lastReset []
2011-07-17 19:20:19 +02:00
2011-07-19 11:16:50 +02:00
minSize _ (SystrayState _ systrayScreen _ _ icons) height screen = case True of
2011-07-19 12:49:05 +02:00
_ | screen == systrayScreen -> max 0 $ (length icons)*(height+2)-1
| otherwise -> 0
2011-07-17 19:20:19 +02:00
weight _ = 0
render Systray (SystrayState phi systrayScreen reset lastResetRef icons) x y w h screen = case True of
_ | screen == systrayScreen -> do
2011-07-19 11:16:50 +02:00
lastReset <- liftIO $ readIORef lastResetRef
liftIO $ writeIORef lastResetRef reset
forM_ (zip [0..] icons) $ \(i, SystrayIconState midParent window) -> do
let x' = x + i*(h+2)
sendMessage phi $ RenderIcon midParent window x' y h h (lastReset /= reset)
2011-07-19 11:16:50 +02:00
| otherwise -> return ()
2011-07-19 11:16:50 +02:00
handleMessage _ priv@(SystrayState phi screen reset lastReset icons) m = case (fromMessage m) of
Just (AddIcon midParent window) -> SystrayState phi screen reset lastReset ((SystrayIconState midParent window):icons)
Just (RemoveIcon window) -> SystrayState phi screen reset lastReset $ filter (\(SystrayIconState _ stateWindow) -> stateWindow /= window) icons
_ -> case (fromMessage m) of
Just ResetBackground -> SystrayState phi screen (reset+1) lastReset icons
_ -> priv
2011-07-17 19:20:19 +02:00
systrayRunner :: Phi -> Display -> IO ()
systrayRunner phi dispvar = do
let atoms = getAtoms dispvar
initSuccess <- withDisplay dispvar $ flip initSystray atoms
case initSuccess of
2011-07-19 12:25:08 +02:00
Just xembedWindow -> flip evalStateT M.empty $ do
sendMessage phi HoldShutdown
forever $ do
m <- receiveMessage phi
case (fromMessage m) of
Just event ->
handleEvent event phi dispvar xembedWindow
_ ->
case (fromMessage m) of
Just (RenderIcon midParent window x y w h reset) -> do
withDisplay dispvar $ \disp -> do
liftIO $ flip catch (\_ -> return ()) $ do
sync disp False
2011-07-19 14:50:04 +02:00
setSystrayErrorHandler
2011-07-19 12:25:08 +02:00
(_, x', y', w', h', _, _) <- getGeometry disp midParent
2011-08-11 18:53:02 +02:00
(_, x'', y'', w'', h'', _, _) <- getGeometry disp window
2011-07-19 12:25:08 +02:00
let resize = (fromIntegral x) /= x' || (fromIntegral y) /= y' || (fromIntegral w) /= w' || (fromIntegral h) /= h'
2011-08-11 18:53:02 +02:00
|| 0 /= x'' || 0 /= y'' || (fromIntegral w) /= w'' || (fromIntegral h) /= h''
2011-07-19 12:25:08 +02:00
when resize $ do
moveResizeWindow disp midParent (fromIntegral x) (fromIntegral y) (fromIntegral w) (fromIntegral h)
2011-08-11 18:53:02 +02:00
moveResizeWindow disp window 0 0 (fromIntegral w) (fromIntegral h)
2011-07-19 12:25:08 +02:00
sync disp False
2011-08-11 18:53:02 +02:00
when (resize || reset) $
clearArea disp window 0 0 (fromIntegral w) (fromIntegral h) True
2011-07-19 14:50:04 +02:00
sync disp False
2011-07-19 12:25:08 +02:00
xSetErrorHandler
2011-07-19 14:50:04 +02:00
lastErrorWindow <- liftIO $ getLastErrorWindow
when (lastErrorWindow == window) $ do
2011-08-11 18:53:02 +02:00
removeIcon phi disp True window
2011-07-19 12:25:08 +02:00
_ ->
case (fromMessage m) of
Just Shutdown -> do
windows <- gets M.keys
withDisplay dispvar $ \disp -> do
2011-08-11 18:53:02 +02:00
mapM_ (removeIcon phi disp True) windows
2011-07-19 12:25:08 +02:00
liftIO $ do
destroyWindow disp xembedWindow
sync disp False
sendMessage phi ReleaseShutdown
_ ->
return ()
2011-07-17 19:20:19 +02:00
Nothing ->
return ()
initSystray :: Xlib.Display -> Atoms -> IO (Maybe Window)
initSystray disp atoms = do
currentSystrayWin <- xGetSelectionOwner disp $ atom_NET_SYSTEM_TRAY_SCREEN atoms
if currentSystrayWin /= 0 then do
pid <- liftM (fromMaybe "" . fmap (\pid -> " (pid" ++ show (fromIntegral pid :: CUShort) ++ ")") . join . fmap listToMaybe) $
getWindowProperty16 disp (atom_NET_WM_PID atoms) currentSystrayWin
putStrLn $ "Phi: another systray is running." ++ pid
return Nothing
else do
xembedWin <- createSimpleWindow disp (defaultRootWindow disp) (-1) (-1) 1 1 0 0 0
-- orient horizontally
changeProperty32 disp xembedWin (atom_NET_SYSTEM_TRAY_ORIENTATION atoms) cARDINAL propModeReplace [0]
-- set visual
let rootwin = defaultRootWindow disp
screen = defaultScreen disp
visual = defaultVisual disp screen
visualID = visualIDFromVisual visual
changeProperty32 disp xembedWin (atom_NET_SYSTEM_TRAY_VISUAL atoms) vISUALID propModeReplace [fromIntegral visualID]
xSetSelectionOwner disp (atom_NET_SYSTEM_TRAY_SCREEN atoms) xembedWin currentTime
systrayWin <- xGetSelectionOwner disp $ atom_NET_SYSTEM_TRAY_SCREEN atoms
if systrayWin /= xembedWin then do
destroyWindow disp xembedWin
putStrLn $ "Phi: can't initialize systray."
return Nothing
else do
allocaXEvent $ \event -> do
putClientMessage event rootwin (atomMANAGER atoms) [fromIntegral currentTime, fromIntegral (atom_NET_SYSTEM_TRAY_SCREEN atoms), fromIntegral xembedWin, 0, 0]
sendEvent disp rootwin False structureNotifyMask event
return $ Just xembedWin
sYSTEM_TRAY_REQUEST_DOCK :: CInt
sYSTEM_TRAY_REQUEST_DOCK = 0
sYSTEM_TRAY_BEGIN_MESSAGE :: CInt
sYSTEM_TRAY_BEGIN_MESSAGE = 1
sYSTEM_TRAY_CANCEL_MESSAGE :: CInt
sYSTEM_TRAY_CANCEL_MESSAGE = 2
2011-07-19 11:16:50 +02:00
xEMBED_EMBEDDED_NOTIFY :: CInt
xEMBED_EMBEDDED_NOTIFY = 0
2011-07-17 19:20:19 +02:00
2011-07-19 11:16:50 +02:00
handleEvent :: Event -> Phi -> Display -> Window -> StateT (M.Map Window Window) IO ()
handleEvent message@ClientMessageEvent { ev_message_type = message_type, ev_data = messageData, ev_window = window } phi dispvar xembedWindow = do
2011-07-17 19:20:19 +02:00
let atoms = getAtoms dispvar
2011-07-19 11:16:50 +02:00
screenWindows = getScreenWindows dispvar
2011-07-17 19:20:19 +02:00
when (window == xembedWindow && message_type == atom_NET_SYSTEM_TRAY_OPCODE atoms) $ do
case messageData of
2011-07-19 11:16:50 +02:00
_:opcode:iconID:_ -> do
2011-07-17 19:20:19 +02:00
case True of
2011-07-19 11:16:50 +02:00
_ | opcode == sYSTEM_TRAY_REQUEST_DOCK -> do
when (iconID /= 0) $ withDisplay dispvar $ \disp -> addIcon phi disp (getAtoms dispvar) (snd . head $ screenWindows) $ fromIntegral iconID
| opcode == sYSTEM_TRAY_BEGIN_MESSAGE || opcode == sYSTEM_TRAY_CANCEL_MESSAGE ->
2011-07-17 19:20:19 +02:00
return ()
| otherwise -> do
2011-07-19 11:16:50 +02:00
liftIO $ putStrLn "Phi: unknown tray message"
2011-07-17 19:20:19 +02:00
return ()
_ ->
return ()
2011-07-19 11:16:50 +02:00
handleEvent message@UnmapEvent { ev_window = window } phi dispvar xembedWindow =
2011-08-11 18:53:02 +02:00
withDisplay dispvar $ \disp -> removeIcon phi disp True window
2011-07-19 11:16:50 +02:00
handleEvent message@DestroyWindowEvent { ev_window = window } phi dispvar xembedWindow =
2011-08-11 18:53:02 +02:00
withDisplay dispvar $ \disp -> removeIcon phi disp False window
handleEvent message@AnyEvent { ev_window = window } phi dispvar xembedWindow | ev_event_type message == reparentNotify = do
parent <- liftIO $ alloca $ \rootPtr -> alloca $ \parentPtr -> alloca $ \childrenPtrPtr -> alloca $ \nChildrenPtr -> do
status <- withDisplay dispvar $ \disp -> xQueryTree disp window rootPtr parentPtr childrenPtrPtr nChildrenPtr
case status of
0 ->
return 0
_ -> do
childrenPtr <- peek childrenPtrPtr
when (childrenPtr /= nullPtr) $
xFree childrenPtr >> return ()
peek parentPtr
midParent <- gets $ M.lookup window
when (midParent /= Just parent) $
withDisplay dispvar $ \disp -> removeIcon phi disp False window
return ()
2011-07-19 11:16:50 +02:00
2011-07-17 19:20:19 +02:00
handleEvent _ _ _ _ = return ()
2011-07-19 11:16:50 +02:00
addIcon :: Phi -> Xlib.Display -> Atoms -> Window -> Window -> StateT (M.Map Window Window) IO ()
addIcon phi disp atoms panelWindow window = do
2011-08-11 18:53:02 +02:00
removeIcon phi disp False window
2011-07-19 11:16:50 +02:00
liftIO $ selectInput disp window $ structureNotifyMask .|. propertyChangeMask
midParent <- liftIO $ createSimpleWindow disp panelWindow (-16) (-16) 16 16 0 0 0
liftIO $ do
setWindowBackgroundPixmap disp midParent 1 -- ParentRelative
sync disp False
2011-07-19 14:50:04 +02:00
setSystrayErrorHandler
2011-07-19 11:16:50 +02:00
reparentWindow disp window midParent 0 0
mapRaised disp midParent
mapWindow disp window
allocaXEvent $ \event -> do
putClientMessage event window (atom_XEMBED atoms) [fromIntegral currentTime, fromIntegral xEMBED_EMBEDDED_NOTIFY, 0, fromIntegral midParent, 0]
sendEvent disp window False 0xFFFFFF event
sync disp False
xSetErrorHandler
2011-07-19 14:50:04 +02:00
errorWindow <- liftIO $ getLastErrorWindow
case True of
_ | errorWindow /= window -> do
2011-07-19 11:16:50 +02:00
sendMessage phi $ AddIcon midParent window
sendMessage phi Repaint
modify $ M.insert window midParent
2011-07-19 14:50:04 +02:00
| otherwise ->
2011-07-19 11:16:50 +02:00
liftIO $ destroyWindow disp midParent
2011-08-11 18:53:02 +02:00
removeIcon :: Phi -> Xlib.Display -> Bool -> Window -> StateT (M.Map Window Window) IO ()
removeIcon phi disp reparent window = do
2011-07-19 11:16:50 +02:00
mmidParent <- gets $ M.lookup window
case mmidParent of
Just midParent -> do
sendMessage phi $ RemoveIcon window
sendMessage phi Repaint
liftIO $ do
2011-07-19 12:25:08 +02:00
selectInput disp window $ noEventMask
2011-08-11 18:53:02 +02:00
when reparent $
reparentWindow disp window (defaultRootWindow disp) 0 0
2011-07-19 11:16:50 +02:00
destroyWindow disp midParent
2011-07-19 12:25:08 +02:00
sync disp False
modify $ M.delete window
2011-07-19 11:16:50 +02:00
_ ->
return ()
systray :: Systray
systray = Systray