aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Prompt.hs
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2010-01-24 21:33:24 +0100
committerAdam Vogt <vogt.adam@gmail.com>2010-01-24 21:33:24 +0100
commitef7cd124086bd3c91eb5fea9bb13057a82c71f29 (patch)
tree74912ac97eb5d7bf6013e26c7ede9266f6de6614 /XMonad/Prompt.hs
parent6516064616b0b993a694cb4e8423a53c60a9b3c3 (diff)
downloadXMonadContrib-ef7cd124086bd3c91eb5fea9bb13057a82c71f29.tar.gz
XMonadContrib-ef7cd124086bd3c91eb5fea9bb13057a82c71f29.tar.xz
XMonadContrib-ef7cd124086bd3c91eb5fea9bb13057a82c71f29.zip
Use extensible-exceptions to allow base-3 or base-4
Ignore-this: 136f35fcc0f3a824b96eea0f4e04f276 darcs-hash:20100124203324-1499c-6e811978a61feebf704e3cd7543cbcc0b3e8a0b3.gz
Diffstat (limited to 'XMonad/Prompt.hs')
-rw-r--r--XMonad/Prompt.hs8
1 files changed, 4 insertions, 4 deletions
diff --git a/XMonad/Prompt.hs b/XMonad/Prompt.hs
index d755501..850e0c7 100644
--- a/XMonad/Prompt.hs
+++ b/XMonad/Prompt.hs
@@ -89,7 +89,7 @@ import Data.Set (fromList, toList)
import System.Directory
import System.IO
import System.Posix.Files
-import Control.Exception hiding (handle)
+import Control.Exception.Extensible hiding (handle)
import qualified Data.Map as M
@@ -640,7 +640,7 @@ getCompletions :: XP [String]
getCompletions = do
s <- get
io $ completionFunction s (commandToComplete (xptype s) (command s))
- `catch` \_ -> return []
+ `catch` \(SomeException _) -> return []
setComplWin :: Window -> ComplWindowDim -> XP ()
setComplWin w wi =
@@ -758,7 +758,7 @@ getHistoryFile :: IO FilePath
getHistoryFile = fmap (++ "/history") $ getAppUserDataDirectory "xmonad"
readHistory :: IO History
-readHistory = catch readHist (const (return emptyHistory))
+readHistory = readHist `catch` \(SomeException _) -> return emptyHistory
where
readHist = do
path <- getHistoryFile
@@ -768,7 +768,7 @@ readHistory = catch readHist (const (return emptyHistory))
writeHistory :: History -> IO ()
writeHistory hist = do
path <- getHistoryFile
- catch (writeFile path (show hist)) $ const $ hPutStrLn stderr "error in writing"
+ writeFile path (show hist) `catch` \(SomeException _) -> hPutStrLn stderr "error in writing"
setFileMode path mode
where mode = ownerReadMode .|. ownerWriteMode