{-# LANGUAGE ExistentialQuantification, FlexibleInstances, GeneralizedNewtypeDeriving,
MultiParamTypeClasses, TypeSynonymInstances, DeriveDataTypeable #-}
module XMonad.Core (
X, WindowSet, WindowSpace, WorkspaceId,
ScreenId(..), ScreenDetail(..), XState(..),
XConf(..), XConfig(..), LayoutClass(..),
Layout(..), readsLayout, Typeable, Message,
SomeMessage(..), fromMessage, LayoutMessages(..),
StateExtension(..), ExtensionClass(..),
runX, catchX, userCode, userCodeDef, io, catchIO, installSignalHandlers, uninstallSignalHandlers,
withDisplay, withWindowSet, isRoot, runOnWorkspaces,
getAtom, spawn, spawnPID, xfork, recompile, trace, whenJust, whenX,
getXMonadDir, getXMonadCacheDir, getXMonadDataDir, stateFileName,
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, atom_WM_TAKE_FOCUS, withWindowAttributes,
ManageHook, Query(..), runQuery
) where
import XMonad.StackSet hiding (modify)
import Prelude
import Control.Exception.Extensible (fromException, try, bracket, throw, finally, SomeException(..))
import qualified Control.Exception.Extensible as E
import Control.Applicative(Applicative, pure, (<$>), (<*>))
import Control.Monad.Fail
import Control.Monad.State
import Control.Monad.Reader
import Data.Semigroup
import Data.Default
import System.FilePath
import System.IO
import System.Info
import System.Posix.Env (getEnv)
import System.Posix.Process (executeFile, forkProcess, getAnyProcessStatus, createSession)
import System.Posix.Signals
import System.Posix.IO
import System.Posix.Types (ProcessID)
import System.Process
import System.Directory
import System.Exit
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras (getWindowAttributes, WindowAttributes, Event)
import Data.Typeable
import Data.List ((\\))
import Data.Maybe (isJust,fromMaybe)
import Data.Monoid hiding ((<>))
import System.Environment (lookupEnv)
import qualified Data.Map as M
import qualified Data.Set as S
data XState = XState
{ windowset :: !WindowSet
, mapped :: !(S.Set Window)
, waitingUnmap :: !(M.Map Window Int)
, dragging :: !(Maybe (Position -> Position -> X (), X ()))
, numberlockMask :: !KeyMask
, extensibleState :: !(M.Map String (Either String StateExtension))
}
data XConf = XConf
{ display :: Display
, config :: !(XConfig Layout)
, theRoot :: !Window
, normalBorder :: !Pixel
, focusedBorder :: !Pixel
, keyActions :: !(M.Map (KeyMask, KeySym) (X ()))
, buttonActions :: !(M.Map (KeyMask, Button) (Window -> X ()))
, mouseFocused :: !Bool
, mousePosition :: !(Maybe (Position, Position))
, currentEvent :: !(Maybe Event)
}
data XConfig l = XConfig
{ normalBorderColor :: !String
, focusedBorderColor :: !String
, terminal :: !String
, layoutHook :: !(l Window)
, manageHook :: !ManageHook
, handleEventHook :: !(Event -> X All)
, workspaces :: ![String]
, modMask :: !KeyMask
, keys :: !(XConfig Layout -> M.Map (ButtonMask,KeySym) (X ()))
, mouseBindings :: !(XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ()))
, borderWidth :: !Dimension
, logHook :: !(X ())
, startupHook :: !(X ())
, focusFollowsMouse :: !Bool
, clickJustFocuses :: !Bool
, clientMask :: !EventMask
, rootMask :: !EventMask
, handleExtraArgs :: !([String] -> XConfig Layout -> IO (XConfig Layout))
}
type WindowSet = StackSet WorkspaceId (Layout Window) Window ScreenId ScreenDetail
type WindowSpace = Workspace WorkspaceId (Layout Window) Window
type WorkspaceId = String
newtype ScreenId = S Int deriving (Eq,Ord,Show,Read,Enum,Num,Integral,Real)
data ScreenDetail = SD { screenRect :: !Rectangle } deriving (Eq,Show, Read)
newtype X a = X (ReaderT XConf (StateT XState IO) a)
deriving (Functor, Monad, MonadFail, MonadIO, MonadState XState, MonadReader XConf, Typeable)
instance Applicative X where
pure = return
(<*>) = ap
instance Semigroup a => Semigroup (X a) where
(<>) = liftM2 (<>)
instance (Monoid a) => Monoid (X a) where
mempty = return mempty
mappend = liftM2 mappend
instance Default a => Default (X a) where
def = return def
type ManageHook = Query (Endo WindowSet)
newtype Query a = Query (ReaderT Window X a)
deriving (Functor, Applicative, Monad, MonadReader Window, MonadIO)
runQuery :: Query a -> Window -> X a
runQuery (Query m) w = runReaderT m w
instance Semigroup a => Semigroup (Query a) where
(<>) = liftM2 (<>)
instance Monoid a => Monoid (Query a) where
mempty = return mempty
mappend = liftM2 mappend
instance Default a => Default (Query a) where
def = return def
runX :: XConf -> XState -> X a -> IO (a, XState)
runX c st (X a) = runStateT (runReaderT a c) st
catchX :: X a -> X a -> X a
catchX job errcase = do
st <- get
c <- ask
(a, s') <- io $ runX c st job `E.catch` \e -> case fromException e of
Just x -> throw e `const` (x `asTypeOf` ExitSuccess)
_ -> do hPrint stderr e; runX c st errcase
put s'
return a
userCode :: X a -> X (Maybe a)
userCode a = catchX (Just `liftM` a) (return Nothing)
userCodeDef :: a -> X a -> X a
userCodeDef defValue a = fromMaybe defValue `liftM` userCode a
withDisplay :: (Display -> X a) -> X a
withDisplay f = asks display >>= f
withWindowSet :: (WindowSet -> X a) -> X a
withWindowSet f = gets windowset >>= f
withWindowAttributes :: Display -> Window -> (WindowAttributes -> X ()) -> X ()
withWindowAttributes dpy win f = do
wa <- userCode (io $ getWindowAttributes dpy win)
catchX (whenJust wa f) (return ())
isRoot :: Window -> X Bool
isRoot w = (w==) <$> asks theRoot
getAtom :: String -> X Atom
getAtom str = withDisplay $ \dpy -> io $ internAtom dpy str False
atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, atom_WM_STATE, atom_WM_TAKE_FOCUS :: X Atom
atom_WM_PROTOCOLS = getAtom "WM_PROTOCOLS"
atom_WM_DELETE_WINDOW = getAtom "WM_DELETE_WINDOW"
atom_WM_STATE = getAtom "WM_STATE"
atom_WM_TAKE_FOCUS = getAtom "WM_TAKE_FOCUS"
data Layout a = forall l. (LayoutClass l a, Read (l a)) => Layout (l a)
readsLayout :: Layout a -> String -> [(Layout a, String)]
readsLayout (Layout l) s = [(Layout (asTypeOf x l), rs) | (x, rs) <- reads s]
class Show (layout a) => LayoutClass layout a where
runLayout :: Workspace WorkspaceId (layout a) a
-> Rectangle
-> X ([(a, Rectangle)], Maybe (layout a))
runLayout (Workspace _ l ms) r = maybe (emptyLayout l r) (doLayout l r) ms
doLayout :: layout a -> Rectangle -> Stack a
-> X ([(a, Rectangle)], Maybe (layout a))
doLayout l r s = return (pureLayout l r s, Nothing)
pureLayout :: layout a -> Rectangle -> Stack a -> [(a, Rectangle)]
pureLayout _ r s = [(focus s, r)]
emptyLayout :: layout a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
emptyLayout _ _ = return ([], Nothing)
handleMessage :: layout a -> SomeMessage -> X (Maybe (layout a))
handleMessage l = return . pureMessage l
pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
pureMessage _ _ = Nothing
description :: layout a -> String
description = show
instance LayoutClass Layout Window where
runLayout (Workspace i (Layout l) ms) r = fmap (fmap Layout) `fmap` runLayout (Workspace i l ms) r
doLayout (Layout l) r s = fmap (fmap Layout) `fmap` doLayout l r s
emptyLayout (Layout l) r = fmap (fmap Layout) `fmap` emptyLayout l r
handleMessage (Layout l) = fmap (fmap Layout) . handleMessage l
description (Layout l) = description l
instance Show (Layout a) where show (Layout l) = show l
class Typeable a => Message a
data SomeMessage = forall a. Message a => SomeMessage a
fromMessage :: Message m => SomeMessage -> Maybe m
fromMessage (SomeMessage m) = cast m
instance Message Event
data LayoutMessages = Hide
| ReleaseResources
deriving (Typeable, Eq)
instance Message LayoutMessages
class Typeable a => ExtensionClass a where
initialValue :: a
extensionType :: a -> StateExtension
extensionType = StateExtension
data StateExtension =
forall a. ExtensionClass a => StateExtension a
| forall a. (Read a, Show a, ExtensionClass a) => PersistentExtension a
io :: MonadIO m => IO a -> m a
io = liftIO
catchIO :: MonadIO m => IO () -> m ()
catchIO f = io (f `E.catch` \(SomeException e) -> hPrint stderr e >> hFlush stderr)
spawn :: MonadIO m => String -> m ()
spawn x = spawnPID x >> return ()
spawnPID :: MonadIO m => String -> m ProcessID
spawnPID x = xfork $ executeFile "/bin/sh" False ["-c", x] Nothing
xfork :: MonadIO m => IO () -> m ProcessID
xfork x = io . forkProcess . finally nullStdin $ do
uninstallSignalHandlers
createSession
x
where
nullStdin = do
fd <- openFd "/dev/null" ReadOnly Nothing defaultFileFlags
dupTo fd stdInput
closeFd fd
runOnWorkspaces :: (WindowSpace -> X WindowSpace) -> X ()
runOnWorkspaces job = do
ws <- gets windowset
h <- mapM job $ hidden ws
c:v <- mapM (\s -> (\w -> s { workspace = w}) <$> job (workspace s))
$ current ws : visible ws
modify $ \s -> s { windowset = ws { current = c, visible = v, hidden = h } }
getXMonadDir :: MonadIO m => m String
getXMonadDir =
findFirstDirWithEnv "XMONAD_CONFIG_DIR"
[ getAppUserDataDirectory "xmonad"
, getXDGDirectory XDGConfig "xmonad"
]
getXMonadCacheDir :: MonadIO m => m String
getXMonadCacheDir =
findFirstDirWithEnv "XMONAD_CACHE_DIR"
[ getAppUserDataDirectory "xmonad"
, getXDGDirectory XDGCache "xmonad"
]
getXMonadDataDir :: MonadIO m => m String
getXMonadDataDir =
findFirstDirWithEnv "XMONAD_DATA_DIR"
[ getAppUserDataDirectory "xmonad"
, getXDGDirectory XDGData "xmonad"
]
findFirstDirOf :: MonadIO m => [IO FilePath] -> m FilePath
findFirstDirOf [] = findFirstDirOf [getAppUserDataDirectory "xmonad"]
findFirstDirOf possibles = do
found <- go possibles
case found of
Just path -> return path
Nothing -> do
primary <- io (head possibles)
io (createDirectoryIfMissing True primary)
return primary
where
go [] = return Nothing
go (x:xs) = do
dir <- io x
exists <- io (doesDirectoryExist dir)
if exists then return (Just dir) else go xs
findFirstDirWithEnv :: MonadIO m => String -> [IO FilePath] -> m FilePath
findFirstDirWithEnv envName paths = do
envPath' <- io (getEnv envName)
case envPath' of
Nothing -> findFirstDirOf paths
Just envPath -> findFirstDirOf (return envPath:paths)
getXDGDirectory :: XDGDirectory -> FilePath -> IO FilePath
getXDGDirectory xdgDir suffix =
normalise . (</> suffix) <$>
case xdgDir of
XDGData -> get "XDG_DATA_HOME" ".local/share"
XDGConfig -> get "XDG_CONFIG_HOME" ".config"
XDGCache -> get "XDG_CACHE_HOME" ".cache"
where
get name fallback = do
env <- lookupEnv name
case env of
Nothing -> fallback'
Just path
| isRelative path -> fallback'
| otherwise -> return path
where
fallback' = (</> fallback) <$> getHomeDirectory
data XDGDirectory = XDGData | XDGConfig | XDGCache
stateFileName :: (Functor m, MonadIO m) => m FilePath
stateFileName = (</> "xmonad.state") <$> getXMonadDataDir
recompile :: MonadIO m => Bool -> m Bool
recompile force = io $ do
cfgdir <- getXMonadDir
datadir <- getXMonadDataDir
let binn = "xmonad-"++arch++"-"++os
bin = datadir </> binn
err = datadir </> "xmonad.errors"
src = cfgdir </> "xmonad.hs"
lib = cfgdir </> "lib"
buildscript = cfgdir </> "build"
libTs <- mapM getModTime . Prelude.filter isSource =<< allFiles lib
srcT <- getModTime src
binT <- getModTime bin
useBuildscript <- do
exists <- doesFileExist buildscript
if exists
then do
isExe <- isExecutable buildscript
if isExe
then do
trace $ "XMonad will use build script at " ++ show buildscript ++ " to recompile."
return True
else do
trace $ unlines
[ "XMonad will not use build script, because " ++ show buildscript ++ " is not executable."
, "Suggested resolution to use it: chmod u+x " ++ show buildscript
]
return False
else do
trace $
"XMonad will use ghc to recompile, because " ++ show buildscript ++ " does not exist."
return False
shouldRecompile <-
if useBuildscript || force
then return True
else if any (binT <) (srcT : libTs)
then do
trace "XMonad doing recompile because some files have changed."
return True
else do
trace "XMonad skipping recompile because it is not forced (e.g. via --recompile), and neither xmonad.hs nor any *.hs / *.lhs / *.hsc files in lib/ have been changed."
return False
if shouldRecompile
then do
uninstallSignalHandlers
status <- bracket (openFile err WriteMode) hClose $ \errHandle ->
waitForProcess =<< if useBuildscript
then compileScript bin cfgdir buildscript errHandle
else compileGHC bin cfgdir errHandle
installSignalHandlers
if status == ExitSuccess
then trace "XMonad recompilation process exited with success!"
else do
ghcErr <- readFile err
let msg = unlines $
["Error detected while loading xmonad configuration file: " ++ src]
++ lines (if null ghcErr then show status else ghcErr)
++ ["","Please check the file for errors."]
hPutStrLn stderr msg
forkProcess $ executeFile "xmessage" True ["-default", "okay", replaceUnicode msg] Nothing
return ()
return (status == ExitSuccess)
else return True
where getModTime f = E.catch (Just <$> getModificationTime f) (\(SomeException _) -> return Nothing)
isSource = flip elem [".hs",".lhs",".hsc"] . takeExtension
isExecutable f = E.catch (executable <$> getPermissions f) (\(SomeException _) -> return False)
allFiles t = do
let prep = map (t</>) . Prelude.filter (`notElem` [".",".."])
cs <- prep <$> E.catch (getDirectoryContents t) (\(SomeException _) -> return [])
ds <- filterM doesDirectoryExist cs
concat . ((cs \\ ds):) <$> mapM allFiles ds
replaceUnicode = map $ \c -> case c of
'\8226' -> '*'
'\8216' -> '`'
'\8217' -> '`'
_ -> c
compileGHC bin dir errHandle =
runProcess "ghc" ["--make"
, "xmonad.hs"
, "-i"
, "-ilib"
, "-fforce-recomp"
, "-main-is", "main"
, "-v0"
, "-o", bin
] (Just dir) Nothing Nothing Nothing (Just errHandle)
compileScript bin dir script errHandle =
runProcess script [bin] (Just dir) Nothing Nothing Nothing (Just errHandle)
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust mg f = maybe (return ()) f mg
whenX :: X Bool -> X () -> X ()
whenX a f = a >>= \b -> when b f
trace :: MonadIO m => String -> m ()
trace = io . hPutStrLn stderr
installSignalHandlers :: MonadIO m => m ()
installSignalHandlers = io $ do
installHandler openEndedPipe Ignore Nothing
installHandler sigCHLD Ignore Nothing
(try :: IO a -> IO (Either SomeException a))
$ fix $ \more -> do
x <- getAnyProcessStatus False False
when (isJust x) more
return ()
uninstallSignalHandlers :: MonadIO m => m ()
uninstallSignalHandlers = io $ do
installHandler openEndedPipe Default Nothing
installHandler sigCHLD Default Nothing
return ()