aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Prompt
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--XMonad/Prompt.hs10
-rw-r--r--XMonad/Prompt/DirExec.hs5
-rw-r--r--XMonad/Prompt/RunOrRaise.hs5
-rw-r--r--XMonad/Prompt/Shell.hs7
-rw-r--r--XMonad/Prompt/Ssh.hs6
5 files changed, 13 insertions, 20 deletions
diff --git a/XMonad/Prompt.hs b/XMonad/Prompt.hs
index daa1809..90509d5 100644
--- a/XMonad/Prompt.hs
+++ b/XMonad/Prompt.hs
@@ -68,8 +68,6 @@ module XMonad.Prompt
, XPState
) where
-import Prelude hiding (catch)
-
import XMonad hiding (cleanMask, config)
import qualified XMonad as X (numberlockMask)
import qualified XMonad.StackSet as W
@@ -81,7 +79,7 @@ import Codec.Binary.UTF8.String (decodeString)
import Control.Applicative ((<$>))
import Control.Arrow (first, (&&&), (***))
import Control.Concurrent (threadDelay)
-import Control.Exception.Extensible hiding (handle)
+import Control.Exception.Extensible as E hiding (handle)
import Control.Monad.State
import Data.Bits
import Data.Char (isSpace)
@@ -890,7 +888,7 @@ getCompletions :: XP [String]
getCompletions = do
s <- get
io $ getCompletionFunction s (commandToComplete (currentXPMode s) (command s))
- `catch` \(SomeException _) -> return []
+ `E.catch` \(SomeException _) -> return []
setComplWin :: Window -> ComplWindowDim -> XP ()
setComplWin w wi =
@@ -1028,7 +1026,7 @@ getHistoryFile :: IO FilePath
getHistoryFile = fmap (++ "/history") $ getAppUserDataDirectory "xmonad"
readHistory :: IO History
-readHistory = readHist `catch` \(SomeException _) -> return emptyHistory
+readHistory = readHist `E.catch` \(SomeException _) -> return emptyHistory
where
readHist = do
path <- getHistoryFile
@@ -1039,7 +1037,7 @@ writeHistory :: History -> IO ()
writeHistory hist = do
path <- getHistoryFile
let filtered = M.filter (not . null) hist
- writeFile path (show filtered) `catch` \(SomeException e) ->
+ writeFile path (show filtered) `E.catch` \(SomeException e) ->
hPutStrLn stderr ("error writing history: "++show e)
setFileMode path mode
where mode = ownerReadMode .|. ownerWriteMode
diff --git a/XMonad/Prompt/DirExec.hs b/XMonad/Prompt/DirExec.hs
index ddcc8c5..ef37a9a 100644
--- a/XMonad/Prompt/DirExec.hs
+++ b/XMonad/Prompt/DirExec.hs
@@ -24,8 +24,7 @@ module XMonad.Prompt.DirExec
, DirExec
) where
-import Prelude hiding (catch)
-import Control.Exception
+import Control.Exception as E
import System.Directory
import Control.Monad
import Data.List
@@ -104,4 +103,4 @@ getDirectoryExecutables path =
liftM2 (&&)
(doesFileExist x')
(liftM executable (getPermissions x'))))
- `catch` econst []
+ `E.catch` econst []
diff --git a/XMonad/Prompt/RunOrRaise.hs b/XMonad/Prompt/RunOrRaise.hs
index 8fb5c43..ce93de9 100644
--- a/XMonad/Prompt/RunOrRaise.hs
+++ b/XMonad/Prompt/RunOrRaise.hs
@@ -26,8 +26,7 @@ import XMonad.Prompt.Shell
import XMonad.Actions.WindowGo (runOrRaise)
import XMonad.Util.Run (runProcessWithInput)
-import Prelude hiding (catch)
-import Control.Exception
+import Control.Exception as E
import Control.Monad (liftM, liftM2)
import System.Directory (doesDirectoryExist, doesFileExist, executable, getPermissions)
@@ -71,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` econst 0
+pidof x = io $ (runProcessWithInput "pidof" [x] [] >>= readIO) `E.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 c391ca3..05ee5f4 100644
--- a/XMonad/Prompt/Shell.hs
+++ b/XMonad/Prompt/Shell.hs
@@ -30,10 +30,9 @@ module XMonad.Prompt.Shell
) where
import Codec.Binary.UTF8.String (encodeString)
-import Control.Exception
+import Control.Exception as E
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)
@@ -111,7 +110,7 @@ commandCompletionFunction cmds str | '/' `elem` str = []
getCommands :: IO [String]
getCommands = do
- p <- getEnv "PATH" `catch` econst []
+ p <- getEnv "PATH" `E.catch` econst []
let ds = filter (/= "") $ split ':' p
es <- forM ds $ \d -> do
exists <- doesDirectoryExist d
@@ -142,7 +141,7 @@ isSpecialChar = flip elem " &\\@\"'#?$*()[]{};"
-- In order to /set/ an environment variable (eg. combine with a prompt so you can modify @$HTTP_PROXY@ dynamically),
-- you need to use 'System.Posix.putEnv'.
env :: String -> String -> IO String
-env variable fallthrough = getEnv variable `catch` econst fallthrough
+env variable fallthrough = getEnv variable `E.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 c3a035d..e9e7ec8 100644
--- a/XMonad/Prompt/Ssh.hs
+++ b/XMonad/Prompt/Ssh.hs
@@ -19,15 +19,13 @@ module XMonad.Prompt.Ssh
Ssh,
) 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.Exception as E
import Control.Monad
import Data.Maybe
@@ -78,7 +76,7 @@ sshComplListLocal = do
sshComplListGlobal :: IO [String]
sshComplListGlobal = do
- env <- getEnv "SSH_KNOWN_HOSTS" `catch` econst "/nonexistent"
+ env <- getEnv "SSH_KNOWN_HOSTS" `E.catch` econst "/nonexistent"
fs <- mapM fileExists [ env
, "/usr/local/etc/ssh/ssh_known_hosts"
, "/usr/local/etc/ssh_known_hosts"