-- | Functions for formatting and spawning shell commands -- -- TLDR: spawning a "command" in xmonad is complicated for weird reasons, and -- this solution is the most sane (for me) given the constraints of the xmonad -- codebase. -- -- A few facts about xmonad (and window managers in general): -- 1) It is single-threaded (since X is single threaded) -- 2) Because of (1), it ignores SIGCHLD, which means any subprocess started -- by xmonad will instantly be reaped after spawning. This guarantees the -- main thread running the WM will never be blocked. -- -- In general, this means that 'System.Process.waitForProcess' (and similar) -- will not work since these call wait() on the child process, which will fail -- because the child has already been cleared and thus there is nothing on which -- to wait. By extension this also means we don't have access to a child's exit -- code. -- -- XMonad and contrib use their own method of spawning subprocesses using the -- extremely low-level 'System.Process.Posix' API. See the code for -- 'XMonad.Core.spawn' or 'XMonad.Util.Run.safeSpawn'. Specifically, the -- sequence is (in terms of the low level Linux API): -- 1) call fork() -- 2) uninstall signal handlers -- 3) call setsid() -- 4) start new thing with exec() -- -- In practice, I'm guessing the main reason for 2 and 3 is so that child -- processes don't inherit the weird SIGCHLD behavior of xmonad itself. The -- setsid thing is one way to guarantee that killing the child thread will also -- kill its children (if any). Note that this obviously will not block since -- we are calling fork() without wait() (which would throw an error anyways). -- -- What if I actually want the exit code? -- -- The best solution (I can come up with), is to use bracket to uninstall -- handlers, run process (with wait), and then reinstall handlers. I can use -- this with a much higher-level interface which will make things easier. This -- obviously means that if the process is running in the main thread, it needs -- to be almost instantaneous (since it actually will be blocking). NOTE: I -- shouldn't use this to replace the existing functions in xmonad since -- 'spawning' a new process in a non-blocking manner with a higher-level API -- will produce lots of Haskell objects that need to be cleaned, and it will be -- hard (perhaps impossible) to keep track and deal with these after spawning. -- -- This works, albeit with the cost of using almost every process API in Haskell. -- -- Briefly: -- 1) 'System.Process.Posix' (where xmonad lives) -- 2) 'System.Process' (wraps 1) -- 2) 'System.Process.Typed' (wraps 2, which I prefer for getting exit codes) -- 3) 'RIO.Process' (wraps 3, which I prefer at the app level) {-# LANGUAGE OverloadedStrings #-} module XMonad.Internal.Shell ( fmtCmd , spawnCmd , spawn , spawnPipe , doubleQuote , singleQuote , skip , runProcess , proc , shell , (#!&&) , (#!||) , (#!|) , (#!>>) ) where import RIO import qualified RIO.Text as T import qualified System.Process.Typed as P import qualified XMonad.Core as X import qualified XMonad.Util.Run as XR -------------------------------------------------------------------------------- -- | Opening subshell -- https://github.com/xmonad/xmonad/issues/113 withDefaultSignalHandlers :: IO a -> IO a withDefaultSignalHandlers = bracket_ X.uninstallSignalHandlers X.installSignalHandlers addGroupSession :: P.ProcessConfig x y z -> P.ProcessConfig x y z addGroupSession = P.setCreateGroup True . P.setNewSession True runProcess :: P.ProcessConfig a b c -> IO ExitCode runProcess = withDefaultSignalHandlers . P.runProcess shell :: T.Text -> P.ProcessConfig () () () shell = addGroupSession . P.shell . T.unpack proc :: FilePath -> [T.Text] -> P.ProcessConfig () () () proc cmd args = addGroupSession $ P.proc cmd (T.unpack <$> args) spawn :: MonadIO m => T.Text -> m () spawn = X.spawn . T.unpack -- spawnAt :: MonadIO m => FilePath -> T.Text -> m () -- spawnAt fp = liftIO . void . startProcess . P.setWorkingDir fp . shell spawnPipe :: MonadIO m => T.Text -> m Handle spawnPipe = XR.spawnPipe . T.unpack spawnCmd :: MonadIO m => FilePath -> [T.Text] -> m () spawnCmd cmd = spawn . fmtCmd cmd -------------------------------------------------------------------------------- -- | Formatting commands fmtCmd :: FilePath -> [T.Text] -> T.Text fmtCmd cmd args = T.unwords $ T.pack cmd : args op :: T.Text -> T.Text -> T.Text -> T.Text op a x b = T.unwords [a, x, b] (#!&&) :: T.Text -> T.Text -> T.Text cmdA #!&& cmdB = op cmdA "&&" cmdB infixr 0 #!&& (#!|) :: T.Text -> T.Text -> T.Text cmdA #!| cmdB = op cmdA "|" cmdB infixr 0 #!| (#!||) :: T.Text -> T.Text -> T.Text cmdA #!|| cmdB = op cmdA "||" cmdB infixr 0 #!|| (#!>>) :: T.Text -> T.Text -> T.Text cmdA #!>> cmdB = op cmdA ";" cmdB infixr 0 #!>> doubleQuote :: T.Text -> T.Text doubleQuote s = T.concat ["\"", s, "\""] singleQuote :: T.Text -> T.Text singleQuote s = T.concat ["'", s, "'"] skip :: Monad m => m () skip = return ()