xman/app/Main.hs

239 lines
8.6 KiB
Haskell
Raw Normal View History

2020-03-31 23:15:43 -04:00
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
2020-04-01 12:57:39 -04:00
--------------------------------------------------------------------------------
2020-04-01 12:59:35 -04:00
-- | Xcape MANager (XMan) - a wrapper for managing xcape
2020-04-01 12:57:39 -04:00
--
2020-04-01 12:59:35 -04:00
-- xcape is a program to map keyrelease events to keysyms, and is very useful
-- for making custom keymaps. However, it is not always desirable to have this
-- running all the time; for example, VirtualBox will blend the xkb keymap with
-- that if the Guest OS, so xcape may end up producing an extra keypress. The
-- solution is to turn off xcape when certain windows are in focus.
2020-04-01 12:57:39 -04:00
--
-- The process for doing this using Xlib:
-- 1) Listen for PropertyNotify events from the root window
-- 2) Of those events, filter those where the _NET_ACTIVE_WINDOW atom has changed
2020-04-01 16:51:28 -04:00
-- 3) Using the value of _NET_ACTIVE_WINDOW, get the app name of the active window
-- 4) If the app name matches a certain criteria, turn off xcape (vice versa)
2020-04-01 12:57:39 -04:00
--
-- The matching criteria in (4) are POSIX regular expressions.
2020-04-01 13:02:17 -04:00
--
-- Known limitations:
-- this is agnostic to any keymap changes, so if the keymap is changed, xcape
-- will not be updated or restarted. Furthermore, it is outside the scope of
-- this program to bind multiple xcape mappings with multiple keymaps
2020-04-01 12:57:39 -04:00
module Main (main) where
2020-03-31 23:15:43 -04:00
2022-07-23 00:38:24 -04:00
import Control.Monad
2020-03-31 23:15:43 -04:00
import Control.Monad.Reader
import Control.Monad.State
import Data.Maybe (isJust)
import Graphics.X11.Types
import Graphics.X11.Xlib.Atom
import Graphics.X11.Xlib.Display
import Graphics.X11.Xlib.Event
import Graphics.X11.Xlib.Extras
import Graphics.X11.Xlib.Misc
import Graphics.X11.Xlib.Types
import Text.Regex.TDFA
import System.Directory
2020-03-31 23:15:43 -04:00
import System.Environment
import System.Posix.IO
import System.Posix.Signals
import System.Process
2020-04-01 12:57:39 -04:00
--------------------------------------------------------------------------------
-- | Central State+Reader+IO Monad (I wonder where this idea came from...)
--
2020-04-01 12:59:35 -04:00
-- The Reader portion holds some of the key data structures from X that we care
-- about as well as the regular expression patterns to match the app names we
-- care about and and the bindings to pass to the xcape command.
2020-04-01 12:57:39 -04:00
--
2020-04-01 12:59:35 -04:00
-- The State portion holds the xcape process handle (so we can kill it later)
2020-03-31 23:15:43 -04:00
newtype XMan a = XMan (ReaderT XMConf (StateT XMState IO) a) deriving
(Functor, Monad, MonadIO, MonadState XMState, MonadReader XMConf)
instance Applicative XMan where
pure = return
(<*>) = ap
2020-04-01 16:47:10 -04:00
newtype XMState = XMState { xcapeHandle :: Maybe ProcessHandle }
2020-03-31 23:15:43 -04:00
data XMConf = XMConf
{ display :: Display
, theRoot :: Window
, netActiveWindow :: Atom
, regexps :: Patterns
2020-04-01 16:47:10 -04:00
, xcapeProcess :: CreateProcess
2020-03-31 23:15:43 -04:00
}
2020-04-01 16:47:10 -04:00
-- | timeout for xcape
type Timeout = Maybe String
-- | bindings for xcape
type Bindings = String
2020-04-01 16:47:10 -04:00
-- | regular expression patterns
type Patterns = [String]
-- | window app name
type AppName = String
2020-04-01 13:02:17 -04:00
--------------------------------------------------------------------------------
2020-04-01 12:57:39 -04:00
main :: IO ()
main = getArgs >>= parse
2020-03-31 23:15:43 -04:00
2020-04-01 12:57:39 -04:00
-- | Given a list of arguments, either start the program or print the usage
2020-03-31 23:15:43 -04:00
parse :: [String] -> IO ()
2020-04-01 16:47:10 -04:00
parse [_] = usage
parse ("-t":t:b:rs) = initXMan rs $ mkXcapeProcess (Just t) b
parse (b:rs) = initXMan rs $ mkXcapeProcess Nothing b
parse _ = usage
2022-07-23 00:38:24 -04:00
-- | The name of the xcape executable
xcapeExe :: String
xcapeExe = "xcape"
2020-04-01 16:47:10 -04:00
-- | Given a timeout and bindings for xcape, return a process record. This will
-- run xcape in debug mode (which will make it run as a foreground process,
-- otherwise it will fork unnecessarily).
mkXcapeProcess :: Timeout -> Bindings -> CreateProcess
mkXcapeProcess (Just t) b = proc xcapeExe $ ["-t", t, "-d", "-e"] ++ [b]
mkXcapeProcess Nothing b = proc xcapeExe $ ["-d", "-e"] ++ [b]
2020-03-31 23:15:43 -04:00
2020-04-01 12:57:39 -04:00
-- | Print the usage and exit
2020-03-31 23:15:43 -04:00
usage :: IO ()
2020-04-01 16:47:10 -04:00
usage = putStrLn "xman [-t TIMEOUT] BINDINGS REGEXP [[REGEXP] ...]"
2020-03-31 23:15:43 -04:00
-- | Given xcape bindings and regular expression patterns to match the window
-- titles we care about, initialize the XMan monad and run the main event loop
2020-04-01 16:47:10 -04:00
initXMan :: Patterns -> CreateProcess -> IO ()
initXMan rs cp = do
r <- checkXcape
if r then initX else putStrLn "could not find xcape binary"
where
initX = do
-- ignore SIGCHLD so we don't produce zombie processes
void $ installHandler sigCHLD Ignore Nothing
dpy <- openDisplay ""
root <- rootWindow dpy $ defaultScreen dpy
naw <- internAtom dpy "_NET_ACTIVE_WINDOW" False
let cf = XMConf
{ display = dpy
, theRoot = root
, netActiveWindow = naw
, regexps = rs
, xcapeProcess = cp
}
st = XMState { xcapeHandle = Nothing }
-- listen only for PropertyNotify events on the root window
allocaSetWindowAttributes $ \a -> do
set_event_mask a propertyChangeMask
changeWindowAttributes dpy root cWEventMask a
void $ allocaXEvent $ \e ->
runXMan cf st $ do
updateXCape -- set the initial state before entering main loop
forever $ handle =<< io (nextEvent dpy e >> getEvent e)
2022-07-23 00:38:24 -04:00
-- | Return true if xcape is installed
checkXcape :: IO Bool
checkXcape = isJust <$> findExecutable xcapeExe
2020-04-01 12:57:39 -04:00
-- | Lift an IO monad into the XMan context
io :: MonadIO m => IO a -> m a
io = liftIO
-- | Given an initial state and configuration, run the XMan monad
runXMan :: XMConf -> XMState -> XMan a -> IO (a, XMState)
runXMan c s (XMan a) = runStateT (runReaderT a c) s
-- | Update the xcape status given the state of XMan
2020-03-31 23:15:43 -04:00
updateXCape :: XMan ()
updateXCape = do
dpy <- asks display
atom <- asks netActiveWindow
root <- asks theRoot
2022-07-21 23:29:38 -04:00
-- find the active window; if none are found, assume there are no windows
-- open, in which case xcape should be running
2020-03-31 23:15:43 -04:00
prop <- io $ getWindowProperty32 dpy atom root
case prop of
Just [aw] -> getAppName (fromIntegral aw) >>= startOrKillXCape
2022-07-21 23:29:38 -04:00
_ -> startXCape
2020-03-31 23:15:43 -04:00
2020-04-01 12:57:39 -04:00
-- | Given an event, call a handler. In this case the only thing we care about
-- are PropertyNotify events where the atom is _NET_ACTIVE_WINDOW, which will
-- initiated the xcape update logic.
2020-03-31 23:15:43 -04:00
handle :: Event -> XMan ()
handle PropertyEvent { ev_atom = a } = do
atom <- asks netActiveWindow
when (a == atom) updateXCape
handle _ = return ()
-- | Given a window, return its app name
getAppName :: Window -> XMan AppName
getAppName w = io . fmap resName . permitBadWindow . flip getClassHint w =<<
asks display
2020-03-31 23:15:43 -04:00
2020-04-01 12:57:39 -04:00
-- | Given an IO action (which is assumed to call an XLib function that may
-- throw an error), attach an error handler before performing the action and
-- remove it after it completes. The error handler will ignore BadWindow errors
-- (which in this case are assumed to be benign since the _NET_ACTIVE_WINDOW
-- atom may refer to a non-existent window)
2020-03-31 23:15:43 -04:00
permitBadWindow :: IO a -> IO a
permitBadWindow action = do
handler <- mkXErrorHandler $ \_ e ->
getErrorEvent e >>= handleError >> return 0
original <- _xSetErrorHandler handler
res <- action
void $ _xSetErrorHandler original
return res
where
-- TODO also ignore badvalue errors?
handleError ErrorEvent { ev_error_code = t }
| fromIntegral t == badWindow = return ()
handleError _ = print "actual error"
-- | Given an app name, start or stop xcape if it matches any of the supplied
-- regular expressions in XMan
startOrKillXCape :: AppName -> XMan ()
startOrKillXCape name = do
rs <- asks regexps
if any (name =~) rs then stopXCape else startXCape
2020-03-31 23:15:43 -04:00
2020-04-01 12:59:35 -04:00
-- | Start xcape if it is not already running
2020-03-31 23:15:43 -04:00
startXCape :: XMan ()
startXCape = do
2020-04-01 16:47:10 -04:00
pID <- gets xcapeHandle
2020-03-31 23:15:43 -04:00
unless (isJust pID) $ do
2020-04-01 16:47:10 -04:00
cp <- asks xcapeProcess
h <- io $ createProcessNull cp
modify $ \s -> s { xcapeHandle = Just h }
2020-03-31 23:15:43 -04:00
io $ print "started xcape"
2020-04-01 12:59:35 -04:00
-- | Stop xcape if it is running
2020-03-31 23:15:43 -04:00
stopXCape :: XMan ()
stopXCape = do
2020-04-01 16:47:10 -04:00
pID <- gets xcapeHandle
2020-03-31 23:15:43 -04:00
forM_ pID $ \p -> do
io $ terminateProcess p
2020-04-01 16:47:10 -04:00
modify $ \s -> s { xcapeHandle = Nothing }
2020-03-31 23:15:43 -04:00
io $ print "stopped xcape"
2020-04-01 16:47:10 -04:00
-- | Given a createProcess record, start the process with stderr and stdout
-- redirected to the null device
-- NOTE: use the process module here rather than the unix module. The latter has
-- the 'forkProcess' function which may fail if multiple instances of xcape are
-- started and killed in quick succession (Resource unavailable error).
2020-04-01 16:47:10 -04:00
createProcessNull :: CreateProcess -> IO ProcessHandle
createProcessNull cp = do
fd <- openFd "/dev/null" ReadOnly Nothing defaultFileFlags
dn <- UseHandle <$> fdToHandle fd
2020-03-31 23:15:43 -04:00
(_, _, _, h) <- createProcess $ cp { std_err = dn, std_out = dn }
return h