aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2011-11-18 19:47:45 +0100
committerAdam Vogt <vogt.adam@gmail.com>2011-11-18 19:47:45 +0100
commit1187eaf3b7e63523b7ad9bd287038baef3bedfa9 (patch)
tree8989ef70b1ee84a77c1e1de5ace8fc006a355bfb /XMonad
parent1b3327dc7cd7f87aa8dee335889fde734a8ac48b (diff)
downloadXMonadContrib-1187eaf3b7e63523b7ad9bd287038baef3bedfa9.tar.gz
XMonadContrib-1187eaf3b7e63523b7ad9bd287038baef3bedfa9.tar.xz
XMonadContrib-1187eaf3b7e63523b7ad9bd287038baef3bedfa9.zip
Be consistent with core utf8-string usage.
Ignore-this: 9de0599d0fb888c58e11598d4de9599e Now that spawn assumes executeFile takes a String containing utf8 codepoints (and takes an actual String as input) adjust Prompt.Shell to avoid double encoding. U.Run functions are updated to be consistent with spawn. darcs-hash:20111118184745-1499c-0f5bee188cc9540d2747db1adbf87619011a5443.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Prompt/Shell.hs6
-rw-r--r--XMonad/Util/Run.hs11
2 files changed, 10 insertions, 7 deletions
diff --git a/XMonad/Prompt/Shell.hs b/XMonad/Prompt/Shell.hs
index da55f48..8dd151c 100644
--- a/XMonad/Prompt/Shell.hs
+++ b/XMonad/Prompt/Shell.hs
@@ -62,7 +62,7 @@ instance XPrompt Shell where
shellPrompt :: XPConfig -> X ()
shellPrompt c = do
cmds <- io getCommands
- mkXPrompt Shell c (getShellCompl cmds) (spawn . encodeString)
+ mkXPrompt Shell c (getShellCompl cmds) spawn
{- | See safe and unsafeSpawn. prompt is an alias for safePrompt;
safePrompt and unsafePrompt work on the same principles, but will use
@@ -81,9 +81,9 @@ shellPrompt c = do
prompt, unsafePrompt, safePrompt :: FilePath -> XPConfig -> X ()
prompt = unsafePrompt
safePrompt c config = mkXPrompt Shell config (getShellCompl [c]) run
- where run = safeSpawn c . return . encodeString
+ where run = safeSpawn c . return
unsafePrompt c config = mkXPrompt Shell config (getShellCompl [c]) run
- where run a = unsafeSpawn $ c ++ " " ++ encodeString a
+ where run a = unsafeSpawn $ c ++ " " ++ a
getShellCompl :: [String] -> String -> IO [String]
getShellCompl cmds s | s == "" || last s == ' ' = return []
diff --git a/XMonad/Util/Run.hs b/XMonad/Util/Run.hs
index 4b766d8..34c9b5e 100644
--- a/XMonad/Util/Run.hs
+++ b/XMonad/Util/Run.hs
@@ -31,6 +31,7 @@ module XMonad.Util.Run (
hPutStr, hPutStrLn -- re-export for convenience
) where
+import Codec.Binary.UTF8.String
import System.Posix.IO
import System.Posix.Process (createSession, executeFile, forkProcess)
import Control.Concurrent (threadDelay)
@@ -53,7 +54,8 @@ import Control.Monad
-- | Returns the output.
runProcessWithInput :: MonadIO m => FilePath -> [String] -> String -> m String
runProcessWithInput cmd args input = io $ do
- (pin, pout, perr, _) <- runInteractiveProcess cmd args Nothing Nothing
+ (pin, pout, perr, _) <- runInteractiveProcess (encodeString cmd)
+ (map encodeString args) Nothing Nothing
hPutStr pin input
hClose pin
output <- hGetContents pout
@@ -67,7 +69,8 @@ runProcessWithInput cmd args input = io $ do
runProcessWithInputAndWait :: MonadIO m => FilePath -> [String] -> String -> Int -> m ()
runProcessWithInputAndWait cmd args input timeout = io $ do
_ <- xfork $ do
- (pin, pout, perr, _) <- runInteractiveProcess cmd args Nothing Nothing
+ (pin, pout, perr, _) <- runInteractiveProcess (encodeString cmd)
+ (map encodeString args) Nothing Nothing
hPutStr pin input
hFlush pin
threadDelay timeout
@@ -108,7 +111,7 @@ safeSpawn :: MonadIO m => FilePath -> [String] -> m ()
safeSpawn prog args = io $ void_ $ forkProcess $ do
uninstallSignalHandlers
_ <- createSession
- executeFile prog True args Nothing
+ executeFile (encodeString prog) True (map encodeString args) Nothing
where void_ = (>> return ()) -- TODO: replace with Control.Monad.void / void not in ghc6 apparently
-- | Simplified 'safeSpawn'; only takes a program (and no arguments):
@@ -141,6 +144,6 @@ spawnPipe x = io $ do
hSetBuffering h LineBuffering
_ <- xfork $ do
_ <- dupTo rd stdInput
- executeFile "/bin/sh" False ["-c", x] Nothing
+ executeFile "/bin/sh" False ["-c", encodeString x] Nothing
closeFd rd
return h