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

511 lines
19 KiB
Haskell
Raw Normal View History

2011-09-08 19:15:23 +02:00
{-# LANGUAGE GeneralizedNewtypeDeriving, ExistentialQuantification, TypeFamilies, FlexibleContexts, DeriveDataTypeable #-}
2011-09-08 19:15:23 +02:00
module Phi.X11 ( X11(..)
, XEvent(..)
, XMessage(..)
, XConfig(..)
2011-07-12 16:47:24 +02:00
, defaultXConfig
2011-07-14 20:21:30 +02:00
, runPhi
) where
2011-09-08 19:15:23 +02:00
import Graphics.XHB hiding (Window)
2011-10-08 05:12:41 +02:00
import Graphics.XHB.Connection
2011-09-08 19:15:23 +02:00
import qualified Graphics.XHB.Connection.Open as CO
2011-09-07 16:38:36 +02:00
import Graphics.XHB.Gen.Xinerama
2011-09-08 19:15:23 +02:00
import Graphics.XHB.Gen.Xproto hiding (Window)
2011-07-13 02:13:01 +02:00
import Graphics.Rendering.Cairo
import Control.Monad
import Data.Bits
2011-07-13 20:13:04 +02:00
import Data.Char
2011-09-07 16:38:36 +02:00
import Data.List
import Data.Maybe
import Data.Typeable
import Data.Word
import Control.Arrow ((&&&))
2011-07-14 07:34:43 +02:00
import Control.Concurrent
import Control.Concurrent.MVar
2011-08-21 21:39:26 +02:00
import Control.Monad.State.Strict
2011-07-12 16:47:24 +02:00
import Control.Monad.Reader
import Control.Monad.Trans
2011-07-19 12:25:08 +02:00
import System.Exit
import System.Posix.Signals
2011-07-14 07:34:43 +02:00
import System.Posix.Types
2011-09-07 16:38:36 +02:00
import qualified Phi.Bindings.XCB as XCB
2011-07-14 06:16:04 +02:00
import Phi.Phi
2011-09-07 16:38:36 +02:00
import Phi.X11.Util
2011-07-14 00:09:20 +02:00
import qualified Phi.Types as Phi
2011-07-12 14:41:25 +02:00
import qualified Phi.Panel as Panel
2011-09-08 19:15:23 +02:00
import qualified Phi.Widget as Widget (handleMessage)
import Phi.Widget hiding (handleMessage)
2011-07-12 19:09:05 +02:00
import Phi.X11.Atoms
2011-07-15 09:17:57 +02:00
2011-09-08 19:15:23 +02:00
data X11 = X11 { x11Connection :: !Connection
, x11Atoms :: !Atoms
, x11Screen :: !SCREEN
}
instance Display X11 where
type Window X11 = WINDOW
2011-10-08 05:12:41 +02:00
newtype XEvent = XEvent SomeEvent deriving (Show, Typeable)
2011-09-08 19:15:23 +02:00
data XMessage = UpdateScreens [(Rectangle, WINDOW)] deriving (Show, Typeable)
data XConfig = XConfig { phiXScreenInfo :: !(X11 -> IO [Rectangle])
2011-07-12 16:47:24 +02:00
}
2011-09-08 19:15:23 +02:00
data PhiState w s c = (Widget w s c X11) => PhiState { phiRootImage :: !Surface
, phiPanels :: ![PanelState w s c]
, phiRepaint :: !Bool
, phiShutdown :: !Bool
, phiShutdownHold :: !Int
, phiWidgetState :: !s
}
data PanelState w s c = (Widget w s c X11) => PanelState { panelWindow :: !WINDOW
, panelPixmap :: !PIXMAP
, panelArea :: !Rectangle
, panelScreenArea :: !Rectangle
, panelWidgetCache :: !c
}
2011-08-29 15:10:55 +02:00
data PhiConfig w s c = PhiConfig { phiPhi :: !Phi
, phiPanelConfig :: !Panel.PanelConfig
, phiXConfig :: !XConfig
2011-09-08 19:15:23 +02:00
, phiX11 :: !X11
, phiXCB :: !XCB.Connection
2011-08-29 15:10:55 +02:00
, phiWidget :: !w
}
2011-07-12 16:47:24 +02:00
2011-08-29 15:10:55 +02:00
newtype PhiReader w s c a = PhiReader (ReaderT (PhiConfig w s c) IO a)
deriving (Monad, MonadReader (PhiConfig w s c), MonadIO)
2011-07-12 16:47:24 +02:00
2011-08-29 15:10:55 +02:00
runPhiReader :: PhiConfig w s c -> PhiReader w s c a -> IO a
2011-07-12 16:47:24 +02:00
runPhiReader config (PhiReader a) = runReaderT a config
2011-08-29 15:10:55 +02:00
newtype PhiX w s c a = PhiX (StateT (PhiState w s c) (PhiReader w s c) a)
deriving (Monad, MonadState (PhiState w s c), MonadReader (PhiConfig w s c), MonadIO)
2011-08-29 15:10:55 +02:00
runPhiX :: PhiConfig w s c -> PhiState w s c -> PhiX w s c a -> IO (a, PhiState w s c)
2011-07-14 06:16:04 +02:00
runPhiX config st (PhiX a) = runPhiReader config $ runStateT a st
2011-07-12 16:47:24 +02:00
defaultXConfig = XConfig { phiXScreenInfo = getScreenInfo
}
2011-09-08 19:15:23 +02:00
getScreenInfo :: X11 -> IO [Rectangle]
getScreenInfo x11 = do
let conn = x11Connection x11
screen = x11Screen x11
2011-09-07 16:38:36 +02:00
exs <- queryScreens conn >>= getReply
case exs of
Right xs -> return . map screenInfoToRect $ screen_info_QueryScreensReply xs
2011-09-08 19:15:23 +02:00
Left _ -> getGeometry conn (fromXid . toXid $ root_SCREEN screen) >>= getReply' "getScreenInfo: getGeometry failed" >>=
return . (\(MkGetGeometryReply _ _ x y w h _) -> [Rectangle (fi x) (fi y) (fi w) (fi h)])
2011-09-07 16:38:36 +02:00
where
2011-09-08 19:15:23 +02:00
screenInfoToRect (MkScreenInfo x y w h) = Rectangle (fi x) (fi y) (fi w) (fi h)
fi :: (Integral a, Num b) => a -> b
fi = fromIntegral
2011-09-07 16:38:36 +02:00
2011-09-08 19:15:23 +02:00
runPhi :: (Widget w s c X11) => XConfig -> Panel.PanelConfig -> w -> IO ()
runPhi xconfig config widget = do
2011-07-14 20:21:30 +02:00
phi <- initPhi
2011-07-19 12:25:08 +02:00
installHandler sigTERM (termHandler phi) Nothing
installHandler sigINT (termHandler phi) Nothing
installHandler sigQUIT (termHandler phi) Nothing
2011-09-07 16:38:36 +02:00
conn <- liftM fromJust connect
xcb <- XCB.connect
2011-09-08 19:15:23 +02:00
let dispname = displayInfo conn
screen = (roots_Setup . connectionSetup $ conn) !! CO.screen dispname
2011-09-07 16:38:36 +02:00
atoms <- initAtoms conn
2011-09-08 19:15:23 +02:00
changeWindowAttributes conn (root_SCREEN screen) $ toValueParam [(CWEventMask, toMask [EventMaskPropertyChange, EventMaskStructureNotify])]
2011-07-14 22:50:03 +02:00
bg <- createImageSurface FormatRGB24 1 1
2011-08-29 15:10:55 +02:00
2011-09-08 19:15:23 +02:00
let x11 = X11 conn atoms screen
screens <- liftIO $ phiXScreenInfo xconfig x11
panelWindows <- mapM (createPanelWindow conn screen config) screens
let widget' = widget <~> separator 0 (if weight widget > 0 then 0 else 1)
2011-08-29 15:10:55 +02:00
screenPanels = zip screens panelWindows
2011-09-08 19:15:23 +02:00
initialState <- initWidget widget' phi x11 screenPanels
2011-08-29 15:10:55 +02:00
runPhiX
PhiConfig { phiPhi = phi
, phiXConfig = xconfig
, phiPanelConfig = config
2011-09-08 19:15:23 +02:00
, phiX11 = x11
, phiXCB = xcb
2011-08-29 15:10:55 +02:00
, phiWidget = widget'
}
PhiState { phiRootImage = bg
, phiPanels = []
2011-09-08 01:27:01 +02:00
, phiRepaint = False
2011-08-29 15:10:55 +02:00
, phiShutdown = False
, phiShutdownHold = 0
, phiWidgetState = initialState
} $ do
2011-09-08 19:15:23 +02:00
updateRootImage
2011-09-07 16:38:36 +02:00
2011-09-08 19:15:23 +02:00
panels <- mapM (\(screen, window) -> createPanel window screen) screenPanels
2011-09-07 16:38:36 +02:00
2011-09-08 19:15:23 +02:00
forM_ panels setPanelProperties
2011-09-07 16:38:36 +02:00
modify $ \state -> state { phiPanels = panels }
2011-09-08 19:15:23 +02:00
updatePanels
2011-09-08 01:27:01 +02:00
forM_ panels $ liftIO . mapWindow conn . panelWindow
2011-09-07 16:38:36 +02:00
liftIO $ forkIO $ receiveEvents phi conn
2011-07-14 20:21:30 +02:00
forever $ do
available <- messageAvailable phi
repaint <- gets phiRepaint
2011-10-07 05:31:23 +02:00
when (not available && repaint) $ liftIO $ threadDelay 30000
available <- messageAvailable phi
when (not available && repaint) $ do
2011-09-08 19:15:23 +02:00
updatePanels
modify $ \state -> state {phiRepaint = False}
2011-07-15 09:17:57 +02:00
message <- receiveMessage phi
2011-09-08 19:15:23 +02:00
handleMessage message
2011-07-19 12:25:08 +02:00
2011-09-09 03:20:16 +02:00
2011-07-19 12:25:08 +02:00
case (fromMessage message) of
Just Shutdown ->
modify $ \state -> state { phiShutdown = True }
Just HoldShutdown ->
modify $ \state -> state { phiShutdownHold = phiShutdownHold state + 1 }
Just ReleaseShutdown ->
modify $ \state -> state { phiShutdownHold = phiShutdownHold state - 1 }
_ ->
return ()
shutdown <- gets phiShutdown
shutdownHold <- gets phiShutdownHold
when (shutdown && (shutdownHold == 0)) $
liftIO $ exitSuccess
return ()
2011-07-19 12:25:08 +02:00
termHandler :: Phi -> Handler
termHandler phi = Catch $ sendMessage phi Shutdown
2011-09-08 19:15:23 +02:00
handleMessage :: (Widget w s c X11) => Message -> PhiX w s c ()
handleMessage m = do
2011-08-29 15:10:55 +02:00
w <- asks phiWidget
modify $ \state -> state {phiWidgetState = Widget.handleMessage w (phiWidgetState state) m}
2011-07-14 20:21:30 +02:00
case (fromMessage m) of
Just Repaint ->
modify $ \state -> state {phiRepaint = True}
2011-07-14 20:21:30 +02:00
_ ->
case (fromMessage m) of
2011-09-07 16:38:36 +02:00
Just (XEvent event) ->
2011-09-08 19:15:23 +02:00
handleEvent event
2011-07-14 20:21:30 +02:00
_ ->
return ()
2011-07-14 07:34:43 +02:00
2011-09-08 19:15:23 +02:00
handleEvent :: (Widget w s c X11) => SomeEvent -> PhiX w s c ()
handleEvent event =
2011-09-07 16:38:36 +02:00
case (fromEvent event) of
2011-09-08 19:15:23 +02:00
Just e -> handlePropertyNotifyEvent e
2011-09-07 16:38:36 +02:00
Nothing -> case (fromEvent event) of
2011-09-08 19:15:23 +02:00
Just e -> handleConfigureNotifyEvent e
2011-09-07 16:38:36 +02:00
Nothing -> return ()
2011-09-08 19:15:23 +02:00
handlePropertyNotifyEvent :: (Widget w s c X11) => PropertyNotifyEvent -> PhiX w s c ()
handlePropertyNotifyEvent MkPropertyNotifyEvent { atom_PropertyNotifyEvent = atom } = do
phi <- asks phiPhi
2011-09-08 19:15:23 +02:00
atoms <- asks (x11Atoms . phiX11)
panels <- gets phiPanels
when (atom == atom_XROOTPMAP_ID atoms || atom == atom_XROOTMAP_ID atoms) $ do
2011-09-08 19:15:23 +02:00
updateRootImage
sendMessage phi ResetBackground
sendMessage phi Repaint
2011-09-08 19:15:23 +02:00
handleConfigureNotifyEvent :: (Widget w s c X11) => ConfigureNotifyEvent -> PhiX w s c ()
handleConfigureNotifyEvent MkConfigureNotifyEvent { window_ConfigureNotifyEvent = window } = do
x11 <- asks phiX11
let conn = x11Connection x11
screen = x11Screen x11
rootWindow = root_SCREEN screen
when (window == rootWindow) $ do
phi <- asks phiPhi
xconfig <- asks phiXConfig
config <- asks phiPanelConfig
panels <- gets phiPanels
let screens = map panelScreenArea panels
screens' <- liftIO $ phiXScreenInfo xconfig x11
2011-09-08 19:15:23 +02:00
when (screens /= screens') $ do
liftIO $ do
mapM_ (freePixmap conn . panelPixmap) panels
mapM_ (destroyWindow conn . panelWindow) $ drop (length screens') panels
let panelsScreens = zip screens' $ map Just panels ++ repeat Nothing
panels' <- forM panelsScreens $ \(screenarea, mpanel) ->
case mpanel of
Just panel -> do
let rect = panelBounds config screenarea
win = panelWindow panel
2011-10-08 05:12:41 +02:00
liftIO $ configureWindow conn $ MkConfigureWindow win (toMask [ConfigWindowX, ConfigWindowY, ConfigWindowWidth, ConfigWindowHeight]) $
toValueParam [ (ConfigWindowX, fromIntegral $ rect_x rect)
, (ConfigWindowY, fromIntegral $ rect_y rect)
, (ConfigWindowWidth, fromIntegral $ rect_width rect)
, (ConfigWindowHeight, fromIntegral $ rect_height rect)
]
2011-09-08 19:15:23 +02:00
panel' <- createPanel win screenarea
setPanelProperties panel'
return panel'
Nothing -> do
win <- liftIO $ createPanelWindow conn screen config screenarea
panel <- createPanel win screenarea
setPanelProperties panel
liftIO $ mapWindow conn $ panelWindow panel
return panel
modify $ \state -> state { phiPanels = panels' }
sendMessage phi $ UpdateScreens $ map (panelScreenArea &&& panelWindow) panels'
sendMessage phi Repaint
2011-10-07 05:31:23 +02:00
maybeReceiveEvents' :: Connection -> IO [XEvent]
maybeReceiveEvents' conn = do
yield
mevent <- pollForEvent conn
case mevent of
Just event ->
liftM2 (:) (return . XEvent $ event) (maybeReceiveEvents' conn)
Nothing ->
return []
receiveEvents' :: Connection -> IO [XEvent]
receiveEvents' conn = do
liftM2 (:) (liftM XEvent $ waitForEvent conn) (maybeReceiveEvents' conn)
2011-09-07 16:38:36 +02:00
receiveEvents :: Phi -> Connection -> IO ()
2011-10-07 05:31:23 +02:00
receiveEvents phi conn =
forever $ receiveEvents' conn >>= sendMessages phi
2011-09-08 19:15:23 +02:00
updatePanels :: (Widget w s c X11) => PhiX w s c ()
updatePanels = do
X11 conn _ screen <- asks phiX11
xcb <- asks phiXCB
2011-08-29 15:10:55 +02:00
w <- asks phiWidget
s <- gets phiWidgetState
2011-07-14 22:50:03 +02:00
rootImage <- gets phiRootImage
panels <- gets phiPanels
2011-07-13 02:13:01 +02:00
2011-07-14 00:09:20 +02:00
panels' <- forM panels $ \panel -> do
2011-07-19 11:16:50 +02:00
let pixmap = panelPixmap panel
2011-07-14 22:50:03 +02:00
area = panelArea panel
2011-08-21 21:39:26 +02:00
(panelSurfaces, cache') <- liftIO $ flip runStateT (panelWidgetCache panel) $
2011-09-08 19:15:23 +02:00
(withDimension area $ render w s 0 0) (panelScreenArea panel)
2011-07-19 11:16:50 +02:00
2011-09-08 19:15:23 +02:00
let visualtype = fromJust $ findVisualtype screen (root_visual_SCREEN screen)
2011-09-07 16:38:36 +02:00
xbuffer <- liftIO $ withDimension area $ XCB.createXCBSurface xcb (fromXid . toXid $ pixmap) visualtype
liftIO $ (withDimension area $ withSimilarSurface xbuffer ContentColor) $ \buffer -> do
renderWith buffer $ do
save
2011-09-08 19:15:23 +02:00
translate (-(fromIntegral $ rect_x area)) (-(fromIntegral $ rect_y area))
2011-09-07 16:38:36 +02:00
withPatternForSurface rootImage $ \pattern -> do
patternSetExtend pattern ExtendRepeat
setSource pattern
paint
restore
forM_ panelSurfaces $ \(updated, SurfaceSlice x surface) -> do
save
2011-09-07 16:38:36 +02:00
translate (fromIntegral x) 0
withPatternForSurface surface setSource
paint
restore
2011-07-19 11:16:50 +02:00
2011-09-07 16:38:36 +02:00
renderWith xbuffer $ do
withPatternForSurface buffer setSource
paint
surfaceFinish xbuffer
2011-07-14 22:50:03 +02:00
2011-09-07 16:38:36 +02:00
-- update window
liftIO $ withDimension area $ XCB.clearArea xcb True (panelWindow panel) 0 0
2011-08-29 15:10:55 +02:00
return $ panel { panelWidgetCache = cache' }
2011-07-19 11:16:50 +02:00
2011-07-14 00:09:20 +02:00
modify $ \state -> state { phiPanels = panels' }
2011-09-08 19:15:23 +02:00
updateRootImage :: PhiX w s c ()
updateRootImage = do
X11 conn atoms screen <- asks phiX11
xcb <- asks phiXCB
2011-07-14 22:50:03 +02:00
2011-09-08 19:15:23 +02:00
let visualtype = fromJust $ findVisualtype screen (root_visual_SCREEN screen)
2011-09-07 16:38:36 +02:00
rootwin = root_SCREEN screen
2011-07-22 11:42:22 +02:00
2011-09-07 16:38:36 +02:00
pixmap <- liftM (fromXid . toXid . fromMaybe 0 . listToMaybe . join . catMaybes) $ forM [atom_XROOTPMAP_ID atoms, atom_XROOTMAP_ID atoms] $
\atom -> liftIO $ getProperty32 conn rootwin atom
(pixmapWidth, pixmapHeight) <- case (fromXid . toXid $ (pixmap :: PIXMAP) :: Word32) of
2011-08-29 15:10:55 +02:00
0 -> return (1, 1)
2011-09-07 16:38:36 +02:00
_ -> liftIO $ getGeometry conn (fromXid . toXid $ pixmap) >>= getReply' "updateRootImage: getGeometry failed" >>= return . (width_GetGeometryReply &&& height_GetGeometryReply)
2011-07-14 22:50:03 +02:00
-- update surface size
oldBg <- gets phiRootImage
imageWidth <- liftM fromIntegral $ imageSurfaceGetWidth oldBg
imageHeight <- liftM fromIntegral $ imageSurfaceGetHeight oldBg
when (imageWidth /= pixmapWidth || imageHeight /= pixmapHeight) $ do
2011-07-14 22:50:03 +02:00
surfaceFinish oldBg
newBg <- liftIO $ createImageSurface FormatRGB24 (fromIntegral pixmapWidth) (fromIntegral pixmapHeight)
2011-07-14 22:50:03 +02:00
modify $ \state -> state { phiRootImage = newBg }
bg <- gets phiRootImage
2011-09-07 16:38:36 +02:00
case (fromXid . toXid $ pixmap :: Word32) of
0 -> do
renderWith bg $ do
setSourceRGB 0 0 0
paint
_ -> do
2011-09-07 16:38:36 +02:00
rootSurface <- liftIO $ XCB.createXCBSurface xcb (fromXid . toXid $ pixmap) visualtype (fromIntegral pixmapWidth) (fromIntegral pixmapHeight)
renderWith bg $ withPatternForSurface rootSurface $ \pattern -> do
setSource pattern
paint
surfaceFinish rootSurface
2011-09-07 16:38:36 +02:00
return ()
2011-09-08 19:15:23 +02:00
createPanel :: (Widget w s c X11) => WINDOW -> Rectangle -> PhiX w s c (PanelState w s c)
createPanel win screenRect = do
(conn, screen) <- asks $ (x11Connection &&& x11Screen) . phiX11
2011-07-12 16:47:24 +02:00
config <- asks phiPanelConfig
2011-08-29 15:10:55 +02:00
w <- asks phiWidget
2011-07-13 02:13:01 +02:00
let rect = panelBounds config screenRect
2011-09-07 16:38:36 +02:00
depth = root_depth_SCREEN screen
2011-07-19 11:16:50 +02:00
2011-09-07 16:38:36 +02:00
pixmap <- liftIO $ newResource conn
liftIO $ createPixmap conn $ withDimension rect $ MkCreatePixmap depth pixmap (fromXid . toXid $ win)
liftIO $ changeWindowAttributes conn win $ toValueParam [(CWBackPixmap, fromXid . toXid $ pixmap)]
2011-07-13 02:13:01 +02:00
2011-07-14 20:21:30 +02:00
return PanelState { panelWindow = win
2011-07-19 11:16:50 +02:00
, panelPixmap = pixmap
2011-07-14 20:21:30 +02:00
, panelArea = rect
, panelScreenArea = screenRect
2011-08-21 21:39:26 +02:00
, panelWidgetCache = initCache w
2011-07-14 20:21:30 +02:00
}
2011-09-08 19:15:23 +02:00
createPanelWindow :: Connection -> SCREEN -> Panel.PanelConfig -> Rectangle -> IO WINDOW
createPanelWindow conn screen config screenRect = do
2011-07-19 11:16:50 +02:00
let rect = panelBounds config screenRect
2011-09-07 16:38:36 +02:00
depth = root_depth_SCREEN screen
rootwin = root_SCREEN screen
visual = root_visual_SCREEN screen
win <- liftIO $ newResource conn
createWindow conn $ (withRectangle rect $ MkCreateWindow depth win rootwin) 0 WindowClassInputOutput visual $
toValueParam [(CWEventMask, toMask [EventMaskExposure]), (CWBackPixel, 0), (CWBorderPixel, 0)]
return win
2011-09-08 19:15:23 +02:00
setPanelProperties :: PanelState w s c -> PhiX w s c ()
setPanelProperties panel = do
(conn, atoms) <- asks $ (x11Connection &&& x11Atoms) . phiX11
liftIO $ do
2011-09-07 16:38:36 +02:00
let name = map (fromIntegral . ord) "Phi"
changeProperty8 conn PropModeReplace (panelWindow panel) (atomWM_NAME atoms) (atomSTRING atoms) name
changeProperty8 conn PropModeReplace (panelWindow panel) (atom_NET_WM_NAME atoms) (atomUTF8_STRING atoms) name
2011-07-13 20:13:04 +02:00
2011-09-07 16:38:36 +02:00
changeProperty32 conn PropModeReplace (panelWindow panel) (atom_NET_WM_WINDOW_TYPE atoms) (atomATOM atoms) [fromXid . toXid $ atom_NET_WM_WINDOW_TYPE_DOCK atoms]
changeProperty32 conn PropModeReplace (panelWindow panel) (atom_NET_WM_DESKTOP atoms) (atomCARDINAL atoms) [0xFFFFFFFF]
changeProperty32 conn PropModeReplace (panelWindow panel) (atom_NET_WM_STATE atoms) (atomATOM atoms) $
map (fromXid . toXid) [ atom_NET_WM_STATE_SKIP_PAGER atoms
, atom_NET_WM_STATE_SKIP_TASKBAR atoms
, atom_NET_WM_STATE_STICKY atoms
, atom_NET_WM_STATE_BELOW atoms
]
2011-07-13 02:13:01 +02:00
2011-09-07 16:38:36 +02:00
changeProperty32 conn PropModeReplace (panelWindow panel) (atom_MOTIF_WM_HINTS atoms) (atom_MOTIF_WM_HINTS atoms) [ 2, 0, 0, 0, 0 ]
2011-07-13 02:13:01 +02:00
2011-09-07 16:38:36 +02:00
changeProperty8 conn PropModeReplace (panelWindow panel) (atomWM_CLASS atoms) (atomSTRING atoms) $ map (fromIntegral . ord) "phi\0Phi"
2011-09-08 19:15:23 +02:00
setStruts panel
2011-09-08 19:15:23 +02:00
setStruts :: PanelState w s c -> PhiX w s c ()
setStruts panel = do
X11 conn atoms screen <- asks phiX11
2011-07-12 16:47:24 +02:00
config <- asks phiPanelConfig
2011-09-08 19:15:23 +02:00
let rootwin = root_SCREEN screen
2011-07-12 16:47:24 +02:00
position = Panel.panelPosition config
area = panelArea panel
2011-09-07 16:38:36 +02:00
rootHeight <- liftIO $ getGeometry conn (fromXid . toXid $ rootwin) >>= getReply' "setStruts: getGeometry failed" >>= return . height_GetGeometryReply
2011-07-12 14:41:25 +02:00
let struts = [makeStruts i | i <- [0..11]]
2011-09-07 16:38:36 +02:00
where
2011-09-08 19:15:23 +02:00
makeTopStruts 2 = (fromIntegral $ rect_y area) + (fromIntegral $ rect_height area)
makeTopStruts 8 = (fromIntegral $ rect_x area)
makeTopStruts 9 = (fromIntegral $ rect_x area) + (fromIntegral $ rect_width area) - 1
2011-09-07 16:38:36 +02:00
makeTopStruts _ = 0
2011-09-08 19:15:23 +02:00
makeBottomStruts 3 = (fromIntegral rootHeight) - (fromIntegral $ rect_y area)
makeBottomStruts 10 = (fromIntegral $ rect_x area)
makeBottomStruts 11 = (fromIntegral $ rect_x area) + (fromIntegral $ rect_width area) - 1
2011-09-07 16:38:36 +02:00
makeBottomStruts _ = 0
makeStruts = case position of
Phi.Top -> makeTopStruts
Phi.Bottom -> makeBottomStruts
liftIO $ do
2011-09-07 16:38:36 +02:00
changeProperty32 conn PropModeReplace (panelWindow panel) (atom_NET_WM_STRUT atoms) (atomCARDINAL atoms) $ take 4 struts
changeProperty32 conn PropModeReplace (panelWindow panel) (atom_NET_WM_STRUT_PARTIAL atoms) (atomCARDINAL atoms) struts
2011-09-08 19:15:23 +02:00
panelBounds :: Panel.PanelConfig -> Rectangle -> Rectangle
2011-07-12 16:47:24 +02:00
panelBounds config screenBounds = case Panel.panelPosition config of
2011-09-08 19:15:23 +02:00
Phi.Top -> screenBounds { rect_height = Panel.panelSize config }
Phi.Bottom -> screenBounds { rect_height = Panel.panelSize config,
rect_y = rect_y screenBounds + rect_height screenBounds - Panel.panelSize config }
2011-09-08 19:15:23 +02:00
withRectangle :: (Num x, Num y, Num w, Num h) => Rectangle -> (x -> y -> w -> h -> a) -> a
withRectangle r = withDimension r . withPosition r
2011-09-08 19:15:23 +02:00
withPosition :: (Num x, Num y) => Rectangle -> (x -> y -> a) -> a
withPosition r f = f (fromIntegral $ rect_x r) (fromIntegral $ rect_y r)
2011-09-08 19:15:23 +02:00
withDimension :: (Num w, Num h) => Rectangle -> (w -> h -> a) -> a
withDimension r f = f (fromIntegral $ rect_width r) (fromIntegral $ rect_height r)