{-# LANGUAGE GeneralizedNewtypeDeriving, ExistentialQuantification #-} module Phi.X11 ( XConfig(..) , defaultXConfig , runPhi ) where import Graphics.X11.Xlib import Graphics.X11.Xlib.Extras import Graphics.X11.Xinerama import Graphics.Rendering.Cairo import Control.Monad import Data.Maybe import Data.Bits import Data.Char 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 Phi.Phi 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 import qualified Phi.Bindings.Util as Util data XConfig = XConfig { phiXScreenInfo :: !(Display -> 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 } runPhi :: (Widget.Widget w s c) => XConfig -> Panel.PanelConfig -> w -> IO () runPhi xconfig config widget = do xSetErrorHandler phi <- initPhi installHandler sigTERM (termHandler phi) Nothing installHandler sigINT (termHandler phi) Nothing installHandler sigQUIT (termHandler phi) Nothing disp <- openDisplay [] atoms <- initAtoms disp selectInput disp (defaultRootWindow disp) $ propertyChangeMask.|.structureNotifyMask bg <- createImageSurface FormatRGB24 1 1 dispmvar <- newMVar disp screens <- liftIO $ phiXScreenInfo xconfig disp panelWindows <- mapM (createPanelWindow disp config) screens let dispvar = Widget.Display dispmvar 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 disp Widget.withDisplay dispvar $ \disp -> do panels <- mapM (\(screen, window) -> createPanel disp window screen) screenPanels forM_ panels $ \panel -> do setPanelProperties disp panel liftIO $ mapWindow disp (panelWindow panel) modify $ \state -> state { phiPanels = panels } liftIO $ forkIO $ receiveEvents phi dispvar forever $ do available <- messageAvailable phi unless available $ do repaint <- gets phiRepaint when repaint $ do updatePanels dispvar modify $ \state -> state {phiRepaint = False} message <- receiveMessage phi handleMessage dispvar 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) => Widget.Display -> Message -> PhiX w s c () handleMessage dispvar 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 event -> Widget.withDisplay dispvar $ flip handleEvent event _ -> return () handleEvent :: (Widget w s c) => Display -> Event -> PhiX w s c () handleEvent disp PropertyEvent { ev_atom = atom } = do phi <- asks phiPhi atoms <- asks phiAtoms panels <- gets phiPanels when (atom == atom_XROOTPMAP_ID atoms || atom == atom_XROOTMAP_ID atoms) $ do updateRootImage disp sendMessage phi ResetBackground sendMessage phi Repaint handleEvent disp ConfigureEvent { ev_window = window } | window == defaultRootWindow disp = do phi <- asks phiPhi xconfig <- asks phiXConfig config <- asks phiPanelConfig panels <- gets phiPanels let screens = map panelScreenArea panels screens' <- liftIO $ phiXScreenInfo xconfig disp when (screens /= screens') $ do liftIO $ do mapM (freePixmap disp . panelPixmap) panels mapM_ (destroyWindow disp . 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 $ withRectangle rect $ moveResizeWindow disp win panel' <- createPanel disp win screen setPanelProperties disp panel' return panel' Nothing -> do win <- liftIO $ createPanelWindow disp config screen panel <- createPanel disp win screen setPanelProperties disp panel liftIO $ mapWindow disp $ panelWindow panel return panel modify $ \state -> state { phiPanels = panels' } sendMessage phi $ UpdateScreens $ map (panelScreenArea &&& panelWindow) panels' sendMessage phi Repaint handleEvent _ _ = return () receiveEvents :: Phi -> Widget.Display -> IO () receiveEvents phi dispvar = do connection <- Widget.withDisplay dispvar $ return . Fd . connectionNumber allocaXEvent $ \xevent -> forever $ do handled <- Widget.withDisplay dispvar $ \disp -> do pend <- pending disp if pend /= 0 then do liftIO $ nextEvent disp xevent event <- liftIO $ Util.getEvent disp xevent sendMessage phi event return True else return False --when (not handled) $ threadWaitRead connection when (not handled) $ threadDelay 40000 updatePanels :: (Widget w s c) => Widget.Display -> PhiX w s c () updatePanels dispvar = 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) Widget.withDisplay dispvar $ \disp -> do let screen = defaultScreen disp visual = defaultVisual disp screen xbuffer <- liftIO $ withDimension area $ Util.createXlibSurface disp pixmap visual liftIO $ (withDimension area $ withSimilarSurface xbuffer ContentColor) $ \buffer -> do renderWith buffer $ do save translate (-(fromIntegral $ rect_x area)) (-(fromIntegral $ rect_y 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 $ do (withDimension area $ clearArea disp (panelWindow panel) 0 0) True sync disp False return $ panel { panelWidgetCache = cache' } modify $ \state -> state { phiPanels = panels' } updateRootImage :: Display -> PhiX w s c () updateRootImage disp = do atoms <- asks phiAtoms let screen = defaultScreen disp visual = defaultVisual disp screen rootwin = defaultRootWindow disp pixmap <- liftM (fromIntegral . fromMaybe 0 . listToMaybe . join . catMaybes) $ forM [atom_XROOTPMAP_ID atoms, atom_XROOTMAP_ID atoms] $ \atom -> liftIO $ getWindowProperty32 disp atom rootwin (pixmapWidth, pixmapHeight) <- case pixmap of 0 -> return (1, 1) _ -> do (_, _, _, pixmapWidth, pixmapHeight, _, _) <- liftIO $ getGeometry disp pixmap return (pixmapWidth, pixmapHeight) -- 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 pixmap of 0 -> do renderWith bg $ do setSourceRGB 0 0 0 paint _ -> do rootSurface <- liftIO $ Util.createXlibSurface disp pixmap visual (fromIntegral pixmapWidth) (fromIntegral pixmapHeight) renderWith bg $ withPatternForSurface rootSurface $ \pattern -> do setSource pattern paint surfaceFinish rootSurface createPanel :: (Widget w s c) => Display -> Window -> Rectangle -> PhiX w s c (PanelState w s c) createPanel disp win screenRect = do config <- asks phiPanelConfig w <- asks phiWidget let rect = panelBounds config screenRect screen = defaultScreen disp depth = defaultDepth disp screen pixmap <- liftIO $ (withDimension rect $ createPixmap disp win) depth liftIO $ setWindowBackgroundPixmap disp win pixmap return PanelState { panelWindow = win , panelPixmap = pixmap , panelArea = rect , panelScreenArea = screenRect , panelWidgetCache = initCache w } createPanelWindow :: Display -> Panel.PanelConfig -> Rectangle -> IO Window createPanelWindow disp config screenRect = do let rect = panelBounds config screenRect screen = defaultScreen disp depth = defaultDepth disp screen visual = defaultVisual disp screen colormap = defaultColormap disp screen rootwin = defaultRootWindow disp mask = cWEventMask.|.cWColormap.|.cWBackPixel.|.cWBorderPixel 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 setPanelProperties :: Display -> PanelState w s c -> PhiX w s c () setPanelProperties disp panel = do atoms <- asks phiAtoms liftIO $ do storeName disp (panelWindow panel) "Phi" changeProperty8 disp (panelWindow panel) (atom_NET_WM_NAME atoms) (atomUTF8_STRING atoms) propModeReplace $ map (fromIntegral . ord) "Phi" 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 } changeProperty32 disp (panelWindow panel) (atom_MOTIF_WM_HINTS atoms) (atom_MOTIF_WM_HINTS atoms) propModeReplace [ 2, 0, 0, 0, 0 ] Util.setClassHint disp (panelWindow panel) ClassHint { resName = "phi", resClass = "Phi" } setStruts disp panel setStruts :: Display -> PanelState w s c -> PhiX w s c () setStruts disp panel = do atoms <- asks phiAtoms config <- asks phiPanelConfig let rootwin = defaultRootWindow disp position = Panel.panelPosition config area = panelArea panel (_, _, _, _, rootHeight, _, _) <- liftIO $ getGeometry disp rootwin 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 Phi.Top -> makeTopStruts Phi.Bottom -> makeBottomStruts liftIO $ do 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 panelBounds :: Panel.PanelConfig -> Rectangle -> Rectangle panelBounds config screenBounds = case Panel.panelPosition config of Phi.Top -> screenBounds { rect_height = fromIntegral $ Panel.panelSize config } Phi.Bottom -> screenBounds { rect_height = fromIntegral $ Panel.panelSize config, rect_y = (rect_y screenBounds) + (fromIntegral $ rect_height 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 $ rect_x r) (fromIntegral $ rect_y r) withDimension :: (Num w, Num h) => Rectangle -> (w -> h -> a) -> a withDimension r f = f (fromIntegral $ rect_width r) (fromIntegral $ rect_height r)