aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Prompt.hs
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2012-11-09 02:35:06 +0100
committerAdam Vogt <vogt.adam@gmail.com>2012-11-09 02:35:06 +0100
commit7f324e08476792e522987867c0f8098eeb0e50e0 (patch)
treeb4deece8dd5395cc8ab39f73f6f36be50c07842f /XMonad/Prompt.hs
parent8210d1d6f72daa3a95dac7be71f3d3358dfe1191 (diff)
downloadXMonadContrib-7f324e08476792e522987867c0f8098eeb0e50e0.tar.gz
XMonadContrib-7f324e08476792e522987867c0f8098eeb0e50e0.tar.xz
XMonadContrib-7f324e08476792e522987867c0f8098eeb0e50e0.zip
Use Control.Exception.catch explitly to avoid warnings
Ignore-this: 2cebdfe604c581f2b4a644e9aed726c7 The base that comes with ghc-7.6.1 no longer includes Prelude.catch; so these modules were changed so that there is no warning for import Prelude hiding (catch) At the same time these changes should be compatible with older GHCs, since the catch being has never been the one in the Prelude. darcs-hash:20121109013506-1499c-c593662b0780eb49287efcbfe0e9796f7dd57c73.gz
Diffstat (limited to '')
-rw-r--r--XMonad/Prompt.hs10
1 files changed, 4 insertions, 6 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