{-# LANGUAGE GeneralizedNewtypeDeriving, ExistentialQuantification #-} module Phi.X11 ( XConfig(..) , defaultXConfig , runPhi ) where import Graphics.XHB import Graphics.XHB.Gen.Xinerama import Graphics.XHB.Gen.Xproto import Graphics.Rendering.Cairo import Control.Monad import Data.Bits import Data.Char import Data.List import Data.Maybe import Data.Typeable import Data.Word import Control.Arrow ((&&&)) import Control.Concurrent import Control.Concurrent.MVar import Control.Monad.State.Strict import Control.Monad.Reader import Control.Monad.Trans import System.Exit import System.Posix.Signals import System.Posix.Types import qualified Phi.Bindings.XCB as XCB import Phi.Phi import Phi.X11.Util import qualified Phi.Types as Phi import qualified Phi.Panel as Panel import qualified Phi.Widget as Widget import Phi.Widget hiding (Display, handleMessage) import Phi.X11.Atoms data XConfig = XConfig { phiXScreenInfo :: !(Connection -> IO [RECTANGLE]) } data PhiState w s c = (Widget.Widget w s c) => PhiState { phiRootImage :: !Surface , phiPanels :: ![PanelState w s c] , phiRepaint :: !Bool , phiShutdown :: !Bool , phiShutdownHold :: !Int , phiWidgetState :: !s } data PanelState w s c = (Widget.Widget w s c) => PanelState { panelWindow :: !WINDOW , panelPixmap :: !PIXMAP , panelArea :: !RECTANGLE , panelScreenArea :: !RECTANGLE , panelWidgetCache :: !c } data PhiConfig w s c = PhiConfig { phiPhi :: !Phi , phiPanelConfig :: !Panel.PanelConfig , phiXConfig :: !XConfig , phiAtoms :: !Atoms , phiWidget :: !w } newtype PhiReader w s c a = PhiReader (ReaderT (PhiConfig w s c) IO a) deriving (Monad, MonadReader (PhiConfig w s c), MonadIO) runPhiReader :: PhiConfig w s c -> PhiReader w s c a -> IO a runPhiReader config (PhiReader a) = runReaderT a config 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) runPhiX :: PhiConfig w s c -> PhiState w s c -> PhiX w s c a -> IO (a, PhiState w s c) runPhiX config st (PhiX a) = runPhiReader config $ runStateT a st defaultXConfig = XConfig { phiXScreenInfo = getScreenInfo } getScreenInfo :: Connection -> IO [RECTANGLE] getScreenInfo conn = do exs <- queryScreens conn >>= getReply case exs of Right xs -> return . map screenInfoToRect $ screen_info_QueryScreensReply xs Left _ -> getGeometry conn (fromXid . toXid $ getRoot conn) >>= getReply' "getScreenInfo: getGeometry failed" >>= return . (\(MkGetGeometryReply _ _ x y w h _) -> [MkRECTANGLE x y w h]) where screenInfoToRect (MkScreenInfo x y w h) = MkRECTANGLE x y w h runPhi :: (Widget.Widget w s c) => XConfig -> Panel.PanelConfig -> w -> IO () runPhi xconfig config widget = do phi <- initPhi installHandler sigTERM (termHandler phi) Nothing installHandler sigINT (termHandler phi) Nothing installHandler sigQUIT (termHandler phi) Nothing conn <- liftM fromJust connect xcb <- XCB.connect atoms <- initAtoms conn changeWindowAttributes conn (getRoot conn) $ toValueParam [(CWEventMask, toMask [EventMaskPropertyChange, EventMaskStructureNotify])] bg <- createImageSurface FormatRGB24 1 1 screens <- liftIO $ phiXScreenInfo xconfig conn panelWindows <- mapM (createPanelWindow conn config) screens let dispvar = Widget.Display conn atoms widget' = widget <~> separator 0 (if weight widget > 0 then 0 else 1) screenPanels = zip screens panelWindows initialState <- Widget.initWidget widget' phi dispvar screenPanels runPhiX PhiConfig { phiPhi = phi , phiXConfig = xconfig , phiPanelConfig = config , phiAtoms = atoms , phiWidget = widget' } PhiState { phiRootImage = bg , phiPanels = [] , phiRepaint = True , phiShutdown = False , phiShutdownHold = 0 , phiWidgetState = initialState } $ do updateRootImage conn xcb panels <- mapM (\(screen, window) -> createPanel conn window screen) screenPanels forM_ panels $ \panel -> do setPanelProperties conn panel liftIO $ mapWindow conn (panelWindow panel) modify $ \state -> state { phiPanels = panels } liftIO $ forkIO $ receiveEvents phi conn forever $ do available <- messageAvailable phi unless available $ do repaint <- gets phiRepaint when repaint $ do updatePanels conn xcb modify $ \state -> state {phiRepaint = False} message <- receiveMessage phi handleMessage conn xcb message 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 () termHandler :: Phi -> Handler termHandler phi = Catch $ sendMessage phi Shutdown handleMessage :: (Widget w s c) => Connection -> XCB.Connection -> Message -> PhiX w s c () handleMessage conn xcb m = do w <- asks phiWidget modify $ \state -> state {phiWidgetState = Widget.handleMessage w (phiWidgetState state) m} case (fromMessage m) of Just Repaint -> modify $ \state -> state {phiRepaint = True} _ -> case (fromMessage m) of Just (XEvent event) -> handleEvent conn xcb event _ -> return () handleEvent :: (Widget w s c) => Connection -> XCB.Connection -> SomeEvent -> PhiX w s c () handleEvent conn xcb event = case (fromEvent event) of Just e -> handlePropertyNotifyEvent conn xcb e Nothing -> case (fromEvent event) of Just e -> handleConfigureNotifyEvent conn e Nothing -> return () handlePropertyNotifyEvent :: (Widget w s c) => Connection -> XCB.Connection -> PropertyNotifyEvent -> PhiX w s c () handlePropertyNotifyEvent conn xcb MkPropertyNotifyEvent { atom_PropertyNotifyEvent = atom } = do phi <- asks phiPhi atoms <- asks phiAtoms panels <- gets phiPanels when (atom == atom_XROOTPMAP_ID atoms || atom == atom_XROOTMAP_ID atoms) $ do updateRootImage conn xcb sendMessage phi ResetBackground sendMessage phi Repaint handleConfigureNotifyEvent :: (Widget w s c) => Connection -> ConfigureNotifyEvent -> PhiX w s c () handleConfigureNotifyEvent conn MkConfigureNotifyEvent { window_ConfigureNotifyEvent = window } | window == getRoot conn = do phi <- asks phiPhi xconfig <- asks phiXConfig config <- asks phiPanelConfig panels <- gets phiPanels let screens = map panelScreenArea panels screens' <- liftIO $ phiXScreenInfo xconfig conn 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 $ \(screen, mpanel) -> case mpanel of Just panel -> do let rect = panelBounds config screen win = panelWindow panel liftIO $ configureWindow conn win $ toValueParam [ (ConfigWindowX, fromIntegral $ x_RECTANGLE rect) , (ConfigWindowY, fromIntegral $ y_RECTANGLE rect) , (ConfigWindowWidth, fromIntegral $ width_RECTANGLE rect) , (ConfigWindowHeight, fromIntegral $ height_RECTANGLE rect) ] panel' <- createPanel conn win screen setPanelProperties conn panel' return panel' Nothing -> do win <- liftIO $ createPanelWindow conn config screen panel <- createPanel conn win screen setPanelProperties conn panel liftIO $ mapWindow conn $ panelWindow panel return panel modify $ \state -> state { phiPanels = panels' } sendMessage phi $ UpdateScreens $ map (panelScreenArea &&& panelWindow) panels' sendMessage phi Repaint handleConfigureNotifyEvent _ _ = return () receiveEvents :: Phi -> Connection -> IO () receiveEvents phi conn = do forever $ waitForEvent conn >>= sendMessage phi . XEvent updatePanels :: (Widget w s c) => Connection -> XCB.Connection -> PhiX w s c () updatePanels conn xcb = do w <- asks phiWidget s <- gets phiWidgetState rootImage <- gets phiRootImage panels <- gets phiPanels panels' <- forM panels $ \panel -> do let pixmap = panelPixmap panel area = panelArea panel (panelSurfaces, cache') <- liftIO $ flip runStateT (panelWidgetCache panel) $ (withDimension area $ Widget.render w s 0 0) (panelScreenArea panel) let screen = head . roots_Setup . connectionSetup $ conn visualtype = fromJust $ findVisualtype screen (root_visual_SCREEN screen) xbuffer <- liftIO $ withDimension area $ XCB.createXCBSurface xcb (fromXid . toXid $ pixmap) visualtype liftIO $ (withDimension area $ withSimilarSurface xbuffer ContentColor) $ \buffer -> do renderWith buffer $ do save translate (-(fromIntegral $ x_RECTANGLE area)) (-(fromIntegral $ y_RECTANGLE area)) withPatternForSurface rootImage $ \pattern -> do patternSetExtend pattern ExtendRepeat setSource pattern paint restore forM_ panelSurfaces $ \(updated, SurfaceSlice x surface) -> do save translate (fromIntegral x) 0 withPatternForSurface surface setSource paint restore renderWith xbuffer $ do withPatternForSurface buffer setSource paint surfaceFinish xbuffer -- update window liftIO $ withDimension area $ XCB.clearArea xcb True (panelWindow panel) 0 0 return $ panel { panelWidgetCache = cache' } modify $ \state -> state { phiPanels = panels' } updateRootImage :: Connection -> XCB.Connection -> PhiX w s c () updateRootImage conn xcb = do atoms <- asks phiAtoms let screen = head . roots_Setup . connectionSetup $ conn visualtype = fromJust $ findVisualtype screen (root_visual_SCREEN screen) rootwin = root_SCREEN screen 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 0 -> return (1, 1) _ -> liftIO $ getGeometry conn (fromXid . toXid $ pixmap) >>= getReply' "updateRootImage: getGeometry failed" >>= return . (width_GetGeometryReply &&& height_GetGeometryReply) -- update surface size oldBg <- gets phiRootImage imageWidth <- liftM fromIntegral $ imageSurfaceGetWidth oldBg imageHeight <- liftM fromIntegral $ imageSurfaceGetHeight oldBg when (imageWidth /= pixmapWidth || imageHeight /= pixmapHeight) $ do surfaceFinish oldBg newBg <- liftIO $ createImageSurface FormatRGB24 (fromIntegral pixmapWidth) (fromIntegral pixmapHeight) modify $ \state -> state { phiRootImage = newBg } bg <- gets phiRootImage case (fromXid . toXid $ pixmap :: Word32) of 0 -> do renderWith bg $ do setSourceRGB 0 0 0 paint _ -> do rootSurface <- liftIO $ XCB.createXCBSurface xcb (fromXid . toXid $ pixmap) visualtype (fromIntegral pixmapWidth) (fromIntegral pixmapHeight) renderWith bg $ withPatternForSurface rootSurface $ \pattern -> do setSource pattern paint surfaceFinish rootSurface return () createPanel :: (Widget w s c) => Connection -> WINDOW -> RECTANGLE -> PhiX w s c (PanelState w s c) createPanel conn win screenRect = do config <- asks phiPanelConfig w <- asks phiWidget let rect = panelBounds config screenRect screen = head . roots_Setup . connectionSetup $ conn depth = root_depth_SCREEN screen pixmap <- liftIO $ newResource conn liftIO $ createPixmap conn $ withDimension rect $ MkCreatePixmap depth pixmap (fromXid . toXid $ win) liftIO $ changeWindowAttributes conn win $ toValueParam [(CWBackPixmap, fromXid . toXid $ pixmap)] return PanelState { panelWindow = win , panelPixmap = pixmap , panelArea = rect , panelScreenArea = screenRect , panelWidgetCache = initCache w } createPanelWindow :: Connection -> Panel.PanelConfig -> RECTANGLE -> IO WINDOW createPanelWindow conn config screenRect = do let rect = panelBounds config screenRect screen = head . roots_Setup . connectionSetup $ conn 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 setPanelProperties :: Connection -> PanelState w s c -> PhiX w s c () setPanelProperties conn panel = do atoms <- asks phiAtoms liftIO $ do 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 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 ] changeProperty32 conn PropModeReplace (panelWindow panel) (atom_MOTIF_WM_HINTS atoms) (atom_MOTIF_WM_HINTS atoms) [ 2, 0, 0, 0, 0 ] changeProperty8 conn PropModeReplace (panelWindow panel) (atomWM_CLASS atoms) (atomSTRING atoms) $ map (fromIntegral . ord) "phi\0Phi" setStruts conn panel setStruts :: Connection -> PanelState w s c -> PhiX w s c () setStruts conn panel = do atoms <- asks phiAtoms config <- asks phiPanelConfig let rootwin = getRoot conn position = Panel.panelPosition config area = panelArea panel rootHeight <- liftIO $ getGeometry conn (fromXid . toXid $ rootwin) >>= getReply' "setStruts: getGeometry failed" >>= return . height_GetGeometryReply let struts = [makeStruts i | i <- [0..11]] where makeTopStruts 2 = (fromIntegral $ y_RECTANGLE area) + (fromIntegral $ height_RECTANGLE area) makeTopStruts 8 = (fromIntegral $ x_RECTANGLE area) makeTopStruts 9 = (fromIntegral $ x_RECTANGLE area) + (fromIntegral $ width_RECTANGLE area) - 1 makeTopStruts _ = 0 makeBottomStruts 3 = (fromIntegral rootHeight) - (fromIntegral $ y_RECTANGLE area) makeBottomStruts 10 = (fromIntegral $ x_RECTANGLE area) makeBottomStruts 11 = (fromIntegral $ x_RECTANGLE area) + (fromIntegral $ width_RECTANGLE area) - 1 makeBottomStruts _ = 0 makeStruts = case position of Phi.Top -> makeTopStruts Phi.Bottom -> makeBottomStruts liftIO $ do 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 panelBounds :: Panel.PanelConfig -> RECTANGLE -> RECTANGLE panelBounds config screenBounds = case Panel.panelPosition config of Phi.Top -> screenBounds { height_RECTANGLE = fromIntegral $ Panel.panelSize config } Phi.Bottom -> screenBounds { height_RECTANGLE = fromIntegral $ Panel.panelSize config, y_RECTANGLE = (y_RECTANGLE screenBounds) + (fromIntegral $ height_RECTANGLE screenBounds) - (fromIntegral $ Panel.panelSize config) } withRectangle :: (Num x, Num y, Num w, Num h) => RECTANGLE -> (x -> y -> w -> h -> a) -> a withRectangle r = withDimension r . withPosition r withPosition :: (Num x, Num y) => RECTANGLE -> (x -> y -> a) -> a withPosition r f = f (fromIntegral $ x_RECTANGLE r) (fromIntegral $ y_RECTANGLE r) withDimension :: (Num w, Num h) => RECTANGLE -> (w -> h -> a) -> a withDimension r f = f (fromIntegral $ width_RECTANGLE r) (fromIntegral $ height_RECTANGLE r)