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

344 lines
13 KiB
Haskell
Raw Normal View History

2011-07-14 20:21:30 +02:00
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
2011-07-12 16:47:24 +02:00
module Phi.X11 ( XConfig(..)
, defaultXConfig
2011-07-14 20:21:30 +02:00
, runPhi
) where
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
import Graphics.X11.Xinerama
2011-07-13 02:13:01 +02:00
import Graphics.Rendering.Cairo
import Control.Monad
import Data.Maybe
import Data.Bits
2011-07-13 20:13:04 +02:00
import Data.Char
2011-07-14 07:34:43 +02:00
import Control.Concurrent
import Control.Concurrent.MVar
import Control.Monad.State
2011-07-12 16:47:24 +02:00
import Control.Monad.Reader
import Control.Monad.Trans
2011-07-14 07:34:43 +02:00
import System.Posix.Types
2011-07-14 06:16:04 +02:00
import Phi.Phi
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-07-14 00:09:20 +02:00
import qualified Phi.Widget as Widget
2011-07-12 19:09:05 +02:00
import Phi.X11.Atoms
2011-07-13 02:13:01 +02:00
import qualified Phi.Bindings.Util as Util
2011-07-15 09:17:57 +02:00
2011-07-14 20:21:30 +02:00
data XConfig = XConfig { phiXScreenInfo :: !(Display -> IO [Rectangle])
2011-07-12 16:47:24 +02:00
}
data PhiState = PhiState { phiRootImage :: !Surface
2011-07-14 20:21:30 +02:00
, phiPanels :: ![PanelState]
, phiRepaint :: !Bool
}
2011-07-14 20:21:30 +02:00
data PanelState = PanelState { panelWindow :: !Window
2011-07-14 22:50:03 +02:00
, panelBuffer :: !Surface
2011-07-14 20:21:30 +02:00
, panelArea :: !Rectangle
, panelScreenArea :: !Rectangle
, panelWidgetStates :: ![Widget.WidgetState]
}
data PhiConfig = PhiConfig { phiPhi :: !Phi
, phiPanelConfig :: !Panel.PanelConfig
2011-07-14 20:21:30 +02:00
, phiXConfig :: !XConfig
, phiAtoms :: !Atoms
2011-07-12 16:47:24 +02:00
}
newtype PhiReader a = PhiReader (ReaderT PhiConfig IO a)
deriving (Monad, MonadReader PhiConfig, MonadIO)
runPhiReader :: PhiConfig -> PhiReader a -> IO a
runPhiReader config (PhiReader a) = runReaderT a config
2011-07-14 06:16:04 +02:00
newtype PhiX a = PhiX (StateT PhiState PhiReader a)
deriving (Monad, MonadState PhiState, MonadReader PhiConfig, MonadIO)
2011-07-14 06:16:04 +02:00
runPhiX :: PhiConfig -> PhiState -> PhiX a -> IO (a, PhiState)
runPhiX config st (PhiX a) = runPhiReader config $ runStateT a st
2011-07-12 16:47:24 +02:00
defaultXConfig = XConfig { phiXScreenInfo = getScreenInfo
}
2011-07-13 02:13:01 +02:00
2011-07-14 20:21:30 +02:00
runPhi :: XConfig -> Panel.PanelConfig -> [Widget.Widget] -> IO ()
runPhi xconfig config widgets = do
2011-07-15 23:54:05 +02:00
xSetErrorHandler
2011-07-14 20:21:30 +02:00
phi <- initPhi
disp <- openDisplay []
2011-07-12 19:09:05 +02:00
atoms <- initAtoms disp
selectInput disp (defaultRootWindow disp) $ propertyChangeMask.|.structureNotifyMask
2011-07-14 22:50:03 +02:00
bg <- createImageSurface FormatRGB24 1 1
runPhiX PhiConfig { phiPhi = phi, phiXConfig = xconfig, phiPanelConfig = config, phiAtoms = atoms } PhiState { phiRootImage = bg, phiPanels = [], phiRepaint = True } $ do
2011-07-14 22:50:03 +02:00
updateRootImage disp
2011-07-12 16:47:24 +02:00
screens <- liftIO $ phiXScreenInfo xconfig disp
2011-07-14 20:21:30 +02:00
2011-07-15 09:17:57 +02:00
dispmvar <- liftIO $ newMVar disp
2011-07-16 15:55:31 +02:00
let dispvar = Widget.Display dispmvar atoms screens
2011-07-14 20:21:30 +02:00
widgetStates <- liftIO $ mapM (Widget.createWidgetState phi dispvar) widgets
2011-07-15 09:17:57 +02:00
Widget.withDisplay dispvar $ \disp -> do
2011-07-14 22:50:03 +02:00
panels <- mapM (createPanel disp widgetStates) screens
forM_ panels $ \panel -> do
setPanelProperties disp panel
liftIO $ mapWindow disp (panelWindow panel)
modify $ \state -> state { phiPanels = panels }
2011-07-14 07:34:43 +02:00
liftIO $ forkIO $ receiveEvents phi dispvar
2011-07-14 20:21:30 +02:00
forever $ do
available <- messageAvailable phi
unless available $ do
repaint <- gets phiRepaint
when repaint $ do
Widget.withDisplay dispvar $ flip updatePanels True
modify $ \state -> state {phiRepaint = False}
2011-07-15 09:17:57 +02:00
message <- receiveMessage phi
2011-07-14 07:34:43 +02:00
handleMessage dispvar message
return ()
2011-07-14 20:21:30 +02:00
handlePanel :: Message -> PanelState -> PanelState
handlePanel message panel@PanelState {panelWidgetStates = widgets} = panel {panelWidgetStates = widgets'}
where
widgets' = Widget.handleMessageWidgets message widgets
2011-07-14 22:50:03 +02:00
handleMessage :: Widget.Display -> Message -> PhiX ()
2011-07-14 20:21:30 +02:00
handleMessage dispvar m = do
modify $ \state@PhiState {phiPanels = panels} -> state {phiPanels = map (handlePanel m) panels}
case (fromMessage m) of
Just Repaint ->
modify $ \state -> state {phiRepaint = True}
2011-07-14 20:21:30 +02:00
_ ->
case (fromMessage m) of
Just ExposeEvent {} ->
Widget.withDisplay dispvar $ flip updatePanels False
Just event@PropertyEvent {} ->
Widget.withDisplay dispvar $ flip handlePropertyUpdate event
2011-07-14 20:21:30 +02:00
_ ->
return ()
2011-07-14 07:34:43 +02:00
2011-07-14 22:50:03 +02:00
receiveEvents :: Phi -> Widget.Display -> IO ()
2011-07-14 07:34:43 +02:00
receiveEvents phi dispvar = do
2011-07-14 22:50:03 +02:00
connection <- Widget.withDisplay dispvar $ return . Fd . connectionNumber
2011-07-14 07:34:43 +02:00
2011-07-14 23:47:38 +02:00
allocaXEvent $ \xevent -> forever $ do
2011-07-14 22:50:03 +02:00
handled <- Widget.withDisplay dispvar $ \disp -> do
2011-07-14 07:34:43 +02:00
pend <- pending disp
if pend /= 0 then
do
liftIO $ nextEvent disp xevent
event <- liftIO $ getEvent xevent
sendMessage phi event
return True
else return False
when (not handled) $ threadWaitRead connection
updatePanels :: Display -> Bool -> PhiX ()
updatePanels disp redraw = do
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-14 22:50:03 +02:00
let buffer = panelBuffer panel
area = panelArea panel
2011-07-14 00:09:20 +02:00
newPanel <- if not redraw then return panel else do
let layoutedWidgets = (withDimension area $ Widget.layoutWidgets (panelWidgetStates panel) 0 0) $ panelScreenArea panel
2011-07-14 00:09:20 +02:00
panel' = panel { panelWidgetStates = layoutedWidgets }
2011-07-14 22:50:03 +02:00
renderWith buffer $ do
withPatternForSurface rootImage $ \pattern -> do
save
translate (-(fromIntegral $ rect_x area)) (-(fromIntegral $ rect_y area))
setSource pattern
paint
restore
2011-07-16 15:55:31 +02:00
Widget.renderWidgets layoutedWidgets $ panelScreenArea panel
2011-07-13 02:13:01 +02:00
2011-07-14 00:09:20 +02:00
return panel'
2011-07-14 22:50:03 +02:00
let screen = defaultScreen disp
visual = defaultVisual disp screen
surface <- liftIO $ withDimension area $ Util.createXlibSurface disp (panelWindow newPanel) visual
-- copy buffer to window
renderWith surface $ withPatternForSurface buffer $ \pattern -> do
setSource pattern
paint
surfaceFinish surface
2011-07-14 00:09:20 +02:00
return newPanel
modify $ \state -> state { phiPanels = panels' }
2011-07-14 07:34:43 +02:00
handlePropertyUpdate :: Display -> Event -> PhiX ()
handlePropertyUpdate disp PropertyEvent { ev_atom = atom } = do
phi <- asks phiPhi
2011-07-12 19:09:05 +02:00
atoms <- asks phiAtoms
panels <- gets phiPanels
2011-07-12 19:09:05 +02:00
when (atom == atom_XROOTPMAP_ID atoms || atom == atom_XROOTMAP_ID atoms) $ do
2011-07-14 22:50:03 +02:00
updateRootImage disp
sendMessage phi Repaint
2011-07-14 22:50:03 +02:00
updateRootImage :: Display -> PhiX ()
updateRootImage disp = do
2011-07-12 19:09:05 +02:00
atoms <- asks phiAtoms
2011-07-14 22:50:03 +02:00
let screen = defaultScreen disp
2011-07-14 22:50:03 +02:00
visual = defaultVisual disp screen
rootwin = defaultRootWindow disp
2011-07-15 09:17:57 +02:00
pixmap <- liftM (fromIntegral . fromMaybe 0 . listToMaybe . join . catMaybes) $ forM [atom_XROOTPMAP_ID atoms, atom_XROOTMAP_ID atoms] $
\atom -> liftIO $ getWindowProperty32 disp atom rootwin
2011-07-14 22:50:03 +02:00
(_, _, _, rootWidth, rootHeight, _, _) <- liftIO $ getGeometry disp rootwin
-- update surface size
oldBg <- gets phiRootImage
imageWidth <- liftM fromIntegral $ imageSurfaceGetWidth oldBg
imageHeight <- liftM fromIntegral $ imageSurfaceGetHeight oldBg
when (imageWidth /= rootWidth || imageHeight /= rootHeight) $ do
surfaceFinish oldBg
newBg <- liftIO $ createImageSurface FormatRGB24 (fromIntegral rootWidth) (fromIntegral rootHeight)
modify $ \state -> state { phiRootImage = newBg }
bg <- gets phiRootImage
rootSurface <- liftIO $ Util.createXlibSurface disp pixmap visual (fromIntegral rootWidth) (fromIntegral rootHeight)
renderWith bg $ withPatternForSurface rootSurface $ \pattern -> do
setSource pattern
paint
surfaceFinish rootSurface
2011-07-14 20:21:30 +02:00
createPanel :: Display -> [Widget.WidgetState] -> Rectangle -> PhiX PanelState
2011-07-14 07:34:43 +02:00
createPanel disp widgets screenRect = do
phi <- asks phiPhi
2011-07-12 16:47:24 +02:00
config <- asks phiPanelConfig
2011-07-13 02:13:01 +02:00
let rect = panelBounds config screenRect
2011-07-14 07:34:43 +02:00
win <- createPanelWindow disp rect
2011-07-13 02:13:01 +02:00
2011-07-14 22:50:03 +02:00
buffer <- liftIO $ withDimension rect $ createImageSurface FormatRGB24
2011-07-13 02:13:01 +02:00
2011-07-14 20:21:30 +02:00
return PanelState { panelWindow = win
2011-07-14 22:50:03 +02:00
, panelBuffer = buffer
2011-07-14 20:21:30 +02:00
, panelArea = rect
, panelScreenArea = screenRect
, panelWidgetStates = widgets
}
2011-07-14 07:34:43 +02:00
createPanelWindow :: Display -> Rectangle -> PhiX Window
createPanelWindow disp rect = do
let screen = defaultScreen disp
depth = defaultDepth disp screen
visual = defaultVisual disp screen
colormap = defaultColormap disp screen
rootwin = defaultRootWindow disp
mask = cWEventMask.|.cWColormap.|.cWBackPixel.|.cWBorderPixel
liftIO $ allocaSetWindowAttributes $ \attr -> do
set_colormap attr colormap
set_background_pixel attr 0
set_border_pixel attr 0
set_event_mask attr exposureMask
withRectangle rect (createWindow disp rootwin) 0 depth inputOutput visual mask attr
2011-07-14 07:34:43 +02:00
setPanelProperties :: Display -> PanelState -> PhiX ()
setPanelProperties disp panel = do
2011-07-12 19:09:05 +02:00
atoms <- asks phiAtoms
liftIO $ do
storeName disp (panelWindow panel) "Phi"
2011-07-13 20:13:04 +02:00
changeProperty8 disp (panelWindow panel) (atom_NET_WM_NAME atoms) (atomUTF8_STRING atoms) propModeReplace $ map (fromIntegral . ord) "Phi"
2011-07-12 19:09:05 +02:00
changeProperty32 disp (panelWindow panel) (atom_NET_WM_WINDOW_TYPE atoms) aTOM propModeReplace [fromIntegral (atom_NET_WM_WINDOW_TYPE_DOCK atoms)]
changeProperty32 disp (panelWindow panel) (atom_NET_WM_DESKTOP atoms) cARDINAL propModeReplace [0xFFFFFFFF]
changeProperty32 disp (panelWindow panel) (atom_NET_WM_STATE atoms) aTOM propModeReplace [ fromIntegral (atom_NET_WM_STATE_SKIP_PAGER atoms)
, fromIntegral (atom_NET_WM_STATE_SKIP_TASKBAR atoms)
, fromIntegral (atom_NET_WM_STATE_STICKY atoms)
, fromIntegral (atom_NET_WM_STATE_BELOW atoms)
]
setWMHints disp (panelWindow panel) WMHints { wmh_flags = fromIntegral inputHintBit
, wmh_input = False
, wmh_initial_state = 0
, wmh_icon_pixmap = 0
, wmh_icon_window = 0
, wmh_icon_x = 0
, wmh_icon_y = 0
, wmh_icon_mask = 0
, wmh_window_group = 0
}
2011-07-12 19:09:05 +02:00
changeProperty32 disp (panelWindow panel) (atom_MOTIF_WM_HINTS atoms) (atom_MOTIF_WM_HINTS atoms) propModeReplace [ 2, 0, 0, 0, 0 ]
2011-07-13 02:13:01 +02:00
Util.setClassHint disp (panelWindow panel) ClassHint { resName = "phi", resClass = "Phi" }
2011-07-14 07:34:43 +02:00
setStruts disp panel
2011-07-14 07:34:43 +02:00
setStruts :: Display -> PanelState -> PhiX ()
setStruts disp panel = do
2011-07-12 19:09:05 +02:00
atoms <- asks phiAtoms
2011-07-12 16:47:24 +02:00
config <- asks phiPanelConfig
let rootwin = defaultRootWindow disp
2011-07-12 16:47:24 +02:00
position = Panel.panelPosition config
area = panelArea panel
(_, _, _, _, rootHeight, _, _) <- liftIO $ getGeometry disp rootwin
2011-07-12 14:41:25 +02:00
let struts = [makeStruts i | i <- [0..11]]
where
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
makeTopStruts _ = 0
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
makeBottomStruts _ = 0
makeStruts = case position of
2011-07-14 00:09:20 +02:00
Phi.Top -> makeTopStruts
Phi.Bottom -> makeBottomStruts
liftIO $ do
2011-07-12 19:09:05 +02:00
changeProperty32 disp (panelWindow panel) (atom_NET_WM_STRUT atoms) cARDINAL propModeReplace $ take 4 struts
changeProperty32 disp (panelWindow panel) (atom_NET_WM_STRUT_PARTIAL atoms) cARDINAL propModeReplace struts
2011-07-12 16:47:24 +02:00
panelBounds :: Panel.PanelConfig -> Rectangle -> Rectangle
panelBounds config screenBounds = case Panel.panelPosition config of
2011-07-14 00:09:20 +02:00
Phi.Top -> screenBounds { rect_height = fromIntegral $ Panel.panelSize config }
Phi.Bottom -> screenBounds { rect_height = fromIntegral $ Panel.panelSize config,
2011-07-12 16:47:24 +02:00
rect_y = (rect_y screenBounds) + (fromIntegral $ rect_height screenBounds) - (fromIntegral $ Panel.panelSize config) }
2011-07-13 02:13:01 +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-07-13 02:13:01 +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-07-13 02:13:01 +02:00
withDimension :: (Num w, Num h) => Rectangle -> (w -> h -> a) -> a
withDimension r f = f (fromIntegral $ rect_width r) (fromIntegral $ rect_height r)