diff options
author | Adam Vogt <vogt.adam@gmail.com> | 2014-05-02 07:58:23 +0200 |
---|---|---|
committer | Adam Vogt <vogt.adam@gmail.com> | 2014-05-02 07:58:23 +0200 |
commit | f945ea48f33119f605cb728a00b5498425fb6293 (patch) | |
tree | b1ecb67e289c6d01bbdf98b39aca1e9b003365b5 | |
parent | a14bbd10b915f8b8a54c1adf6266ba472e85e795 (diff) | |
download | xmonad-f945ea48f33119f605cb728a00b5498425fb6293.tar.gz xmonad-f945ea48f33119f605cb728a00b5498425fb6293.tar.xz xmonad-f945ea48f33119f605cb728a00b5498425fb6293.zip |
avoid warnings from missing Prelude.catch in ghc>
Ignore-this: 3e544b29759ed703e8741f265903210c
darcs-hash:20140502055823-1499c-135896dc7af4c376cdeccac8775dbcf2106f4109.gz
-rw-r--r-- | XMonad/Core.hs | 13 | ||||
-rw-r--r-- | XMonad/ManageHook.hs | 8 |
2 files changed, 11 insertions, 10 deletions
diff --git a/XMonad/Core.hs b/XMonad/Core.hs index 7d2e1cf..cef4f81 100644 --- a/XMonad/Core.hs +++ b/XMonad/Core.hs @@ -31,9 +31,10 @@ module XMonad.Core ( import XMonad.StackSet hiding (modify) -import Prelude hiding ( catch ) +import Prelude import Codec.Binary.UTF8.String (encodeString) -import Control.Exception.Extensible (catch, fromException, try, bracket, throw, finally, SomeException(..)) +import Control.Exception.Extensible (fromException, try, bracket, throw, finally, SomeException(..)) +import qualified Control.Exception.Extensible as E import Control.Applicative import Control.Monad.State import Control.Monad.Reader @@ -178,7 +179,7 @@ catchX :: X a -> X a -> X a catchX job errcase = do st <- get c <- ask - (a, s') <- io $ runX c st job `catch` \e -> case fromException e of + (a, s') <- io $ runX c st job `E.catch` \e -> case fromException e of Just x -> throw e `const` (x `asTypeOf` ExitSuccess) _ -> do hPrint stderr e; runX c st errcase put s' @@ -394,7 +395,7 @@ io = liftIO -- | Lift an 'IO' action into the 'X' monad. If the action results in an 'IO' -- exception, log the exception to stderr and continue normal execution. catchIO :: MonadIO m => IO () -> m () -catchIO f = io (f `catch` \(SomeException e) -> hPrint stderr e >> hFlush stderr) +catchIO f = io (f `E.catch` \(SomeException e) -> hPrint stderr e >> hFlush stderr) -- | spawn. Launch an external application. Specifically, it double-forks and -- runs the 'String' you pass as a command to \/bin\/sh. @@ -489,11 +490,11 @@ recompile force = io $ do return () return (status == ExitSuccess) else return True - where getModTime f = catch (Just <$> getModificationTime f) (\(SomeException _) -> return Nothing) + where getModTime f = E.catch (Just <$> getModificationTime f) (\(SomeException _) -> return Nothing) isSource = flip elem [".hs",".lhs",".hsc"] . takeExtension allFiles t = do let prep = map (t</>) . Prelude.filter (`notElem` [".",".."]) - cs <- prep <$> catch (getDirectoryContents t) (\(SomeException _) -> return []) + cs <- prep <$> E.catch (getDirectoryContents t) (\(SomeException _) -> return []) ds <- filterM doesDirectoryExist cs concat . ((cs \\ ds):) <$> mapM allFiles ds diff --git a/XMonad/ManageHook.hs b/XMonad/ManageHook.hs index 856c742..aa5ae32 100644 --- a/XMonad/ManageHook.hs +++ b/XMonad/ManageHook.hs @@ -18,11 +18,11 @@ module XMonad.ManageHook where -import Prelude hiding (catch) import XMonad.Core import Graphics.X11.Xlib.Extras import Graphics.X11.Xlib (Display, Window, internAtom, wM_NAME) -import Control.Exception.Extensible (bracket, catch, SomeException(..)) +import Control.Exception.Extensible (bracket, SomeException(..)) +import qualified Control.Exception.Extensible as E import Control.Monad.Reader import Data.Maybe import Data.Monoid @@ -74,10 +74,10 @@ title = ask >>= \w -> liftX $ do let getProp = (internAtom d "_NET_WM_NAME" False >>= getTextProperty d w) - `catch` \(SomeException _) -> getTextProperty d w wM_NAME + `E.catch` \(SomeException _) -> getTextProperty d w wM_NAME extract prop = do l <- wcTextPropertyToTextList d prop return $ if null l then "" else head l - io $ bracket getProp (xFree . tp_value) extract `catch` \(SomeException _) -> return "" + io $ bracket getProp (xFree . tp_value) extract `E.catch` \(SomeException _) -> return "" -- | Return the application name. appName :: Query String |