change Dmenu functions to return IO/X (Maybe String)

dmenu exits with code 1 when you hit Escape, and I wanna create a contrib that
takes advantage of that.

This required changes in four contribs (Commands, DirectoryPrompt, ShellPrompt,
and WorkspaceDir), and might require changes in users' Configs. Also, I'm not
sure some of the changes I made to the client code are very Haskelly. Would
appreciate input there.
This commit is contained in:
Devin Mullins
2007-10-06 07:09:59 +00:00
parent dcbfe603b5
commit beaead5256
5 changed files with 22 additions and 12 deletions

View File

@@ -102,7 +102,9 @@ runCommand :: [(String, X ())] -> X ()
runCommand cl = do runCommand cl = do
let m = commandMap cl let m = commandMap cl
choice <- dmenu (M.keys m) choice <- dmenu (M.keys m)
fromMaybe (return ()) (M.lookup choice m) case choice of
Just selection -> fromMaybe (return ()) (M.lookup selection m)
Nothing -> return ()
runCommand' :: String -> X () runCommand' :: String -> X ()
runCommand' c = do runCommand' c = do

View File

@@ -18,6 +18,8 @@ module XMonadContrib.DirectoryPrompt (
directoryPrompt directoryPrompt
) where ) where
import Data.Maybe(fromMaybe)
import XMonad import XMonad
import XMonadContrib.XPrompt import XMonadContrib.XPrompt
import XMonadContrib.Dmenu ( runProcessWithInput ) import XMonadContrib.Dmenu ( runProcessWithInput )
@@ -34,7 +36,7 @@ directoryPrompt :: XPConfig -> String -> (String -> X ()) -> X ()
directoryPrompt c prom job = mkXPrompt (Dir prom) c getDirCompl job directoryPrompt c prom job = mkXPrompt (Dir prom) c getDirCompl job
getDirCompl :: String -> IO [String] getDirCompl :: String -> IO [String]
getDirCompl s = (filter notboring . lines) `fmap` getDirCompl s = (filter notboring . lines . fromMaybe "") `fmap`
runProcessWithInput "/bin/bash" [] ("compgen -A directory " ++ s ++ "\n") runProcessWithInput "/bin/bash" [] ("compgen -A directory " ++ s ++ "\n")
notboring :: String -> Bool notboring :: String -> Bool

View File

@@ -21,6 +21,7 @@ module XMonadContrib.Dmenu (
import XMonad import XMonad
import qualified StackSet as W import qualified StackSet as W
import System.Exit
import System.Process import System.Process
import System.IO import System.IO
import Control.Monad.State import Control.Monad.State
@@ -32,7 +33,9 @@ import Control.Monad.State
-- %import XMonadContrib.Dmenu -- %import XMonadContrib.Dmenu
runProcessWithInput :: FilePath -> [String] -> String -> IO String -- | Returns Just output if the command succeeded, and Nothing if it didn't.
-- This corresponds to dmenu's notion of exit code 1 for a cancelled invocation.
runProcessWithInput :: FilePath -> [String] -> String -> IO (Maybe String)
runProcessWithInput cmd args input = do runProcessWithInput cmd args input = do
(pin, pout, perr, ph) <- runInteractiveProcess cmd args Nothing Nothing (pin, pout, perr, ph) <- runInteractiveProcess cmd args Nothing Nothing
hPutStr pin input hPutStr pin input
@@ -41,16 +44,17 @@ runProcessWithInput cmd args input = do
when (output==output) $ return () when (output==output) $ return ()
hClose pout hClose pout
hClose perr hClose perr
waitForProcess ph exitCode <- waitForProcess ph
return output case exitCode of
ExitSuccess -> return (Just output)
ExitFailure _ -> return Nothing
-- | Starts dmenu on the current screen. Requires this patch to dmenu: -- | Starts dmenu on the current screen. Requires this patch to dmenu:
-- <http://www.jcreigh.com/dmenu/dmenu-3.2-xinerama.patch> -- <http://www.jcreigh.com/dmenu/dmenu-3.2-xinerama.patch>
dmenuXinerama :: [String] -> X String dmenuXinerama :: [String] -> X (Maybe String)
dmenuXinerama opts = do dmenuXinerama opts = do
curscreen <- (fromIntegral . W.screen . W.current) `liftM` gets windowset :: X Int curscreen <- (fromIntegral . W.screen . W.current) `liftM` gets windowset :: X Int
io $ runProcessWithInput "dmenu" ["-xs", show (curscreen+1)] (unlines opts) io $ runProcessWithInput "dmenu" ["-xs", show (curscreen+1)] (unlines opts)
dmenu :: [String] -> X String dmenu :: [String] -> X (Maybe String)
dmenu opts = io $ runProcessWithInput "dmenu" [] (unlines opts) dmenu opts = io $ runProcessWithInput "dmenu" [] (unlines opts)

View File

@@ -58,7 +58,7 @@ shellPrompt c = mkXPrompt Shell c getShellCompl spawn
getShellCompl :: String -> IO [String] getShellCompl :: String -> IO [String]
getShellCompl s getShellCompl s
| s /= "" && last s /= ' ' = do | s /= "" && last s /= ' ' = do
f <- fmap lines $ runProcessWithInput "/bin/bash" [] ("compgen -A file " ++ s ++ "\n") f <- fmap (lines . fromMaybe "") $ runProcessWithInput "/bin/bash" [] ("compgen -A file " ++ s ++ "\n")
c <- commandCompletionFunction s c <- commandCompletionFunction s
hPutStrLn stdout s hPutStrLn stdout s
return $ map escape . sort . nub $ f ++ c return $ map escape . sort . nub $ f ++ c

View File

@@ -68,8 +68,10 @@ workspaceDir :: LayoutClass l a => String -> l a
workspaceDir s = ModifiedLayout (WorkspaceDir s) workspaceDir s = ModifiedLayout (WorkspaceDir s)
scd :: String -> X () scd :: String -> X ()
scd x = do x' <- io (runProcessWithInput "bash" [] ("echo -n " ++ x) `catch` \_ -> return x) scd x = do x' <- io (runProcessWithInput "bash" [] ("echo -n " ++ x) `catch` \_ -> return Nothing)
catchIO $ setCurrentDirectory x' case x' of
Just newDir -> catchIO $ setCurrentDirectory newDir
Nothing -> return ()
changeDir :: XPConfig -> X () changeDir :: XPConfig -> X ()
changeDir c = directoryPrompt c "Set working directory: " (sendMessage . Chdir) changeDir c = directoryPrompt c "Set working directory: " (sendMessage . Chdir)