mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-07-31 04:01:51 -07:00
generalize IO actions to MonadIO m => m actions
This should not cause any working configs to stop working, because IO is an instance of MonadIO, and because complete configs will pin down the type of the call to IO. Note that XMonad.Config.Arossato is not a complete config, and so it needed some tweaks; with a main function, this should not be a problem.
This commit is contained in:
@@ -1,4 +1,5 @@
|
||||
{-# OPTIONS_GHC -fglasgow-exts -fno-warn-missing-signatures #-}
|
||||
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
|
||||
{-# LANGUAGE NoMonomorphismRestriction #-}
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : XMonad.Config.Arossato
|
||||
|
@@ -59,5 +59,5 @@ emailPrompt c addrs =
|
||||
inputPromptWithCompl c "To" (mkComplFunFromList addrs) ?+ \to ->
|
||||
inputPrompt c "Subject" ?+ \subj ->
|
||||
inputPrompt c "Body" ?+ \body ->
|
||||
io $ runProcessWithInput "mail" ["-s", subj, to] (body ++ "\n")
|
||||
runProcessWithInput "mail" ["-s", subj, to] (body ++ "\n")
|
||||
>> return ()
|
||||
|
@@ -37,13 +37,13 @@ import XMonad.Util.Run
|
||||
dmenuXinerama :: [String] -> X String
|
||||
dmenuXinerama opts = do
|
||||
curscreen <- (fromIntegral . W.screen . W.current) `fmap` gets windowset :: X Int
|
||||
io $ runProcessWithInput "dmenu" ["-xs", show (curscreen+1)] (unlines opts)
|
||||
runProcessWithInput "dmenu" ["-xs", show (curscreen+1)] (unlines opts)
|
||||
|
||||
dmenu :: [String] -> X String
|
||||
dmenu opts = menu "dmenu" opts
|
||||
|
||||
menu :: String -> [String] -> X String
|
||||
menu menuCmd opts = io $ runProcessWithInput menuCmd [] (unlines opts)
|
||||
menu menuCmd opts = runProcessWithInput menuCmd [] (unlines opts)
|
||||
|
||||
menuMap :: String -> M.Map String a -> X (Maybe a)
|
||||
menuMap menuCmd selectionMap = do
|
||||
|
@@ -34,7 +34,7 @@ dzen str timeout = dzenWithArgs str [] timeout
|
||||
--
|
||||
-- > dzenWithArgs "Hi, dons!" ["-ta", "r"] (5 `seconds`)
|
||||
dzenWithArgs :: String -> [String] -> Int -> X ()
|
||||
dzenWithArgs str args timeout = io $ runProcessWithInputAndWait "dzen2" args (unchomp str) timeout
|
||||
dzenWithArgs str args timeout = runProcessWithInputAndWait "dzen2" args (unchomp str) timeout
|
||||
-- dzen seems to require the input to terminate with exactly one newline.
|
||||
where unchomp s@['\n'] = s
|
||||
unchomp [] = ['\n']
|
||||
|
@@ -52,8 +52,8 @@ import Control.Monad
|
||||
-- "XMonad.Util.Dzen"
|
||||
|
||||
-- | Returns the output.
|
||||
runProcessWithInput :: FilePath -> [String] -> String -> IO String
|
||||
runProcessWithInput cmd args input = do
|
||||
runProcessWithInput :: MonadIO m => FilePath -> [String] -> String -> m String
|
||||
runProcessWithInput cmd args input = io $ do
|
||||
(pin, pout, perr, _) <- runInteractiveProcess cmd args Nothing Nothing
|
||||
hPutStr pin input
|
||||
hClose pin
|
||||
@@ -65,8 +65,8 @@ runProcessWithInput cmd args input = do
|
||||
return output
|
||||
|
||||
-- | Wait is in µs (microseconds)
|
||||
runProcessWithInputAndWait :: FilePath -> [String] -> String -> Int -> IO ()
|
||||
runProcessWithInputAndWait cmd args input timeout = do
|
||||
runProcessWithInputAndWait :: MonadIO m => FilePath -> [String] -> String -> Int -> m ()
|
||||
runProcessWithInputAndWait cmd args input timeout = io $ do
|
||||
forkProcess $ do
|
||||
(pin, pout, perr, _) <- runInteractiveProcess cmd args Nothing Nothing
|
||||
hPutStr pin input
|
||||
@@ -129,8 +129,8 @@ safeRunInTerm :: String -> String -> X ()
|
||||
safeRunInTerm options command = asks (terminal . config) >>= \t -> safeSpawn t [options, " -e " ++ command]
|
||||
|
||||
-- | Launch an external application through the system shell and return a @Handle@ to its standard input.
|
||||
spawnPipe :: String -> IO Handle
|
||||
spawnPipe x = do
|
||||
spawnPipe :: MonadIO m => String -> m Handle
|
||||
spawnPipe x = io $ do
|
||||
(rd, wr) <- createPipe
|
||||
setFdOption wr CloseOnExec True
|
||||
h <- fdToHandle wr
|
||||
|
Reference in New Issue
Block a user