From 39f010d82d0292d9417a06abaf91dabb43ea3ef4 Mon Sep 17 00:00:00 2001 From: Daniel Wagner Date: Sun, 31 Jul 2011 19:08:50 +0200 Subject: GHC 7 compat Ignore-this: 17a43a709e70ebccc925e016d7057399 * true error: more modules export foldl/foldl'/foldr, so explicitly use the Data.Foldable one * -Werror error: transition from Control.OldException to Control.Exception, assuming everything was IOException darcs-hash:20110731170850-76d51-71271524485f6d10f84521f271182bea5085d400.gz --- XMonad/Prompt/DirExec.hs | 8 ++++++-- XMonad/Prompt/RunOrRaise.hs | 7 ++++++- XMonad/Prompt/Shell.hs | 9 +++++++-- XMonad/Prompt/Ssh.hs | 8 +++++++- 4 files changed, 26 insertions(+), 6 deletions(-) (limited to 'XMonad/Prompt') diff --git a/XMonad/Prompt/DirExec.hs b/XMonad/Prompt/DirExec.hs index 035f9b1..1600f93 100644 --- a/XMonad/Prompt/DirExec.hs +++ b/XMonad/Prompt/DirExec.hs @@ -23,12 +23,17 @@ module XMonad.Prompt.DirExec , dirExecPromptNamed ) where +import Prelude hiding (catch) +import Control.Exception import System.Directory import Control.Monad import Data.List import XMonad import XMonad.Prompt +econst :: Monad m => a -> IOException -> m a +econst = const . return + -- $usage -- 1. In your @~\/.xmonad\/xmonad.hs@: -- @@ -98,5 +103,4 @@ getDirectoryExecutables path = liftM2 (&&) (doesFileExist x') (liftM executable (getPermissions x')))) - `catch` (return . return . show) - + `catch` econst [] diff --git a/XMonad/Prompt/RunOrRaise.hs b/XMonad/Prompt/RunOrRaise.hs index 5fcfb3a..251e09c 100644 --- a/XMonad/Prompt/RunOrRaise.hs +++ b/XMonad/Prompt/RunOrRaise.hs @@ -25,9 +25,14 @@ import XMonad.Prompt.Shell import XMonad.Actions.WindowGo (runOrRaise) import XMonad.Util.Run (runProcessWithInput) +import Prelude hiding (catch) +import Control.Exception import Control.Monad (liftM, liftM2) import System.Directory (doesDirectoryExist, doesFileExist, executable, getPermissions) +econst :: Monad m => a -> IOException -> m a +econst = const . return + {- $usage 1. In your @~\/.xmonad\/xmonad.hs@: @@ -65,7 +70,7 @@ isApp "thunderbird" = className =? "Thunderbird-bin" <||> className =? "Thunderb isApp x = liftM2 (==) pid $ pidof x pidof :: String -> Query Int -pidof x = io $ (runProcessWithInput "pidof" [x] [] >>= readIO) `catch` (\_ -> return 0) +pidof x = io $ (runProcessWithInput "pidof" [x] [] >>= readIO) `catch` econst 0 pid :: Query Int pid = ask >>= (\w -> liftX $ withDisplay $ \d -> getPID d w) diff --git a/XMonad/Prompt/Shell.hs b/XMonad/Prompt/Shell.hs index a8ddff4..9ed9293 100644 --- a/XMonad/Prompt/Shell.hs +++ b/XMonad/Prompt/Shell.hs @@ -25,8 +25,10 @@ module XMonad.Prompt.Shell ) where import Codec.Binary.UTF8.String (decodeString, encodeString) +import Control.Exception import Control.Monad (forM) import Data.List (isPrefixOf) +import Prelude hiding (catch) import System.Directory (doesDirectoryExist, getDirectoryContents) import System.Environment (getEnv) import System.Posix.Files (getFileStatus, isDirectory) @@ -35,6 +37,9 @@ import XMonad.Util.Run import XMonad hiding (config) import XMonad.Prompt +econst :: Monad m => a -> IOException -> m a +econst = const . return + {- $usage 1. In your @~\/.xmonad\/xmonad.hs@: @@ -97,7 +102,7 @@ commandCompletionFunction cmds str | '/' `elem` str = [] getCommands :: IO [String] getCommands = do - p <- getEnv "PATH" `catch` const (return []) + p <- getEnv "PATH" `catch` econst [] let ds = filter (/= "") $ split ':' p es <- forM ds $ \d -> do exists <- doesDirectoryExist d @@ -126,7 +131,7 @@ isSpecialChar = flip elem " &\\@\"'#?$*()[]{};" -- | Ask the shell environment for env :: String -> String -> IO String -env variable fallthrough = getEnv variable `catch` \_ -> return fallthrough +env variable fallthrough = getEnv variable `catch` econst fallthrough {- | Ask the shell what browser the user likes. If the user hasn't defined any $BROWSER, defaults to returning \"firefox\", since that seems to be the most diff --git a/XMonad/Prompt/Ssh.hs b/XMonad/Prompt/Ssh.hs index 122c137..7d84069 100644 --- a/XMonad/Prompt/Ssh.hs +++ b/XMonad/Prompt/Ssh.hs @@ -18,16 +18,22 @@ module XMonad.Prompt.Ssh sshPrompt ) where +import Prelude hiding (catch) + import XMonad import XMonad.Util.Run import XMonad.Prompt import System.Directory import System.Environment +import Control.Exception import Control.Monad import Data.Maybe +econst :: Monad m => a -> IOException -> m a +econst = const . return + -- $usage -- 1. In your @~\/.xmonad\/xmonad.hs@: -- @@ -71,7 +77,7 @@ sshComplListLocal = do sshComplListGlobal :: IO [String] sshComplListGlobal = do - env <- getEnv "SSH_KNOWN_HOSTS" `catch` (\_ -> return "/nonexistent") + env <- getEnv "SSH_KNOWN_HOSTS" `catch` econst "/nonexistent" fs <- mapM fileExists [ env , "/usr/local/etc/ssh/ssh_known_hosts" , "/usr/local/etc/ssh_known_hosts" -- cgit v1.2.3