From d9f831e606e447043239ae4d60e931405132ba37 Mon Sep 17 00:00:00 2001 From: Devin Mullins Date: Sun, 7 Oct 2007 20:59:15 +0200 Subject: Maybe? What Maybe? (rollback earlier dmenu change) darcs-hash:20071007185915-78224-5dc94fbbbc960a853654321317e2b8ba54d8be2a.gz --- Commands.hs | 4 +--- DirectoryPrompt.hs | 4 +--- Dmenu.hs | 18 ++++++++---------- ShellPrompt.hs | 3 +-- WorkspaceDir.hs | 6 ++---- 5 files changed, 13 insertions(+), 22 deletions(-) diff --git a/Commands.hs b/Commands.hs index dcab544..ccb8c55 100644 --- a/Commands.hs +++ b/Commands.hs @@ -102,9 +102,7 @@ runCommand :: [(String, X ())] -> X () runCommand cl = do let m = commandMap cl choice <- dmenu (M.keys m) - case choice of - Just selection -> fromMaybe (return ()) (M.lookup selection m) - Nothing -> return () + fromMaybe (return ()) (M.lookup choice m) runCommand' :: String -> X () runCommand' c = do diff --git a/DirectoryPrompt.hs b/DirectoryPrompt.hs index 5ea4c36..b010d4f 100644 --- a/DirectoryPrompt.hs +++ b/DirectoryPrompt.hs @@ -18,8 +18,6 @@ module XMonadContrib.DirectoryPrompt ( directoryPrompt ) where -import Data.Maybe(fromMaybe) - import XMonad import XMonadContrib.XPrompt import XMonadContrib.Dmenu ( runProcessWithInput ) @@ -36,7 +34,7 @@ directoryPrompt :: XPConfig -> String -> (String -> X ()) -> X () directoryPrompt c prom job = mkXPrompt (Dir prom) c getDirCompl job getDirCompl :: String -> IO [String] -getDirCompl s = (filter notboring . lines . fromMaybe "") `fmap` +getDirCompl s = (filter notboring . lines) `fmap` runProcessWithInput "/bin/bash" [] ("compgen -A directory " ++ s ++ "\n") notboring :: String -> Bool diff --git a/Dmenu.hs b/Dmenu.hs index f2d23fe..cbf2fb7 100644 --- a/Dmenu.hs +++ b/Dmenu.hs @@ -22,7 +22,6 @@ module XMonadContrib.Dmenu ( import XMonad import qualified StackSet as W import qualified Data.Map as M -import System.Exit import System.Process import System.IO import Control.Monad.State @@ -36,7 +35,7 @@ import Control.Monad.State -- | 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 :: FilePath -> [String] -> String -> IO String runProcessWithInput cmd args input = do (pin, pout, perr, ph) <- runInteractiveProcess cmd args Nothing Nothing hPutStr pin input @@ -45,21 +44,20 @@ runProcessWithInput cmd args input = do when (output==output) $ return () hClose pout hClose perr - exitCode <- waitForProcess ph - case exitCode of - ExitSuccess -> return (Just output) - ExitFailure _ -> return Nothing + waitForProcess ph + return output -- | Starts dmenu on the current screen. Requires this patch to dmenu: -- -dmenuXinerama :: [String] -> X (Maybe String) +dmenuXinerama :: [String] -> X String dmenuXinerama opts = do curscreen <- (fromIntegral . W.screen . W.current) `liftM` gets windowset :: X Int io $ runProcessWithInput "dmenu" ["-xs", show (curscreen+1)] (unlines opts) -dmenu :: [String] -> X (Maybe String) +dmenu :: [String] -> X String dmenu opts = io $ runProcessWithInput "dmenu" [] (unlines opts) dmenuMap :: M.Map String a -> X (Maybe a) -dmenuMap selectionMap = - dmenu (M.keys selectionMap) >>= return . maybe Nothing (flip M.lookup selectionMap) +dmenuMap selectionMap = do + selection <- dmenu (M.keys selectionMap) + return $ M.lookup selection selectionMap diff --git a/ShellPrompt.hs b/ShellPrompt.hs index 14e855c..077fd8c 100644 --- a/ShellPrompt.hs +++ b/ShellPrompt.hs @@ -25,7 +25,6 @@ import XMonadContrib.Dmenu import Control.Monad import Data.List -import Data.Maybe import System.Directory import System.IO import System.Environment @@ -58,7 +57,7 @@ shellPrompt c = mkXPrompt Shell c getShellCompl spawn getShellCompl :: String -> IO [String] getShellCompl s | s /= "" && last s /= ' ' = do - f <- fmap (lines . fromMaybe "") $ runProcessWithInput "/bin/bash" [] ("compgen -A file " ++ s ++ "\n") + f <- fmap lines $ runProcessWithInput "/bin/bash" [] ("compgen -A file " ++ s ++ "\n") c <- commandCompletionFunction s hPutStrLn stdout s return . map escape . sort . nub $ f ++ c diff --git a/WorkspaceDir.hs b/WorkspaceDir.hs index 32f548d..97e5f94 100644 --- a/WorkspaceDir.hs +++ b/WorkspaceDir.hs @@ -68,10 +68,8 @@ workspaceDir :: LayoutClass l a => String -> l a workspaceDir s = ModifiedLayout (WorkspaceDir s) scd :: String -> X () -scd x = do x' <- io (runProcessWithInput "bash" [] ("echo -n " ++ x) `catch` \_ -> return Nothing) - case x' of - Just newDir -> catchIO $ setCurrentDirectory newDir - Nothing -> return () +scd x = do x' <- io (runProcessWithInput "bash" [] ("echo -n " ++ x) `catch` \_ -> return x) + catchIO $ setCurrentDirectory x' changeDir :: XPConfig -> X () changeDir c = directoryPrompt c "Set working directory: " (sendMessage . Chdir) -- cgit v1.2.3