xmonad-config/lib/XMonad/Internal/Shell.hs

58 lines
1.4 KiB
Haskell

--------------------------------------------------------------------------------
-- | Functions for formatting and spawning shell commands
module XMonad.Internal.Shell
( fmtCmd
, spawnCmd
, spawnSound
, (#!&&)
, (#!||)
, (#!>>)
) where
import Control.Monad.IO.Class
import System.FilePath.Posix
import XMonad.Core (getXMonadDir)
import XMonad.Internal.Process
--------------------------------------------------------------------------------
-- | Opening subshell
spawnCmd :: MonadIO m => String -> [String] -> m ()
spawnCmd cmd args = spawn $ fmtCmd cmd args
--------------------------------------------------------------------------------
-- | Playing sound
soundDir :: FilePath
soundDir = "sound"
spawnSound :: MonadIO m => FilePath -> m ()
spawnSound file = do
path <- (</> soundDir </> file) <$> getXMonadDir
-- paplay seems to have less latency than aplay
spawnCmd "paplay" [path]
--------------------------------------------------------------------------------
-- | Formatting commands
fmtCmd :: String -> [String] -> String
fmtCmd cmd args = unwords $ cmd : args
(#!&&) :: String -> String -> String
cmdA #!&& cmdB = cmdA ++ " && " ++ cmdB
infixr 0 #!&&
(#!||) :: String -> String -> String
cmdA #!|| cmdB = cmdA ++ " || " ++ cmdB
infixr 0 #!||
(#!>>) :: String -> String -> String
cmdA #!>> cmdB = cmdA ++ "; " ++ cmdB
infixr 0 #!>>