aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Util')
-rw-r--r--XMonad/Util/Font.hs7
-rw-r--r--XMonad/Util/Loggers.hs5
-rw-r--r--XMonad/Util/NamedWindows.hs7
3 files changed, 8 insertions, 11 deletions
diff --git a/XMonad/Util/Font.hs b/XMonad/Util/Font.hs
index 7f66c75..031a706 100644
--- a/XMonad/Util/Font.hs
+++ b/XMonad/Util/Font.hs
@@ -32,11 +32,10 @@ module XMonad.Util.Font
, fi
) where
-import Prelude hiding (catch)
import XMonad
import Foreign
import Control.Applicative
-import Control.Exception
+import Control.Exception as E
import Data.Maybe
#ifdef XFT
@@ -70,7 +69,7 @@ econst = const
initCoreFont :: String -> X FontStruct
initCoreFont s = do
d <- asks display
- io $ catch (getIt d) (fallBack d)
+ io $ E.catch (getIt d) (fallBack d)
where getIt d = loadQueryFont d s
fallBack d = econst $ loadQueryFont d "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
@@ -82,7 +81,7 @@ releaseCoreFont fs = do
initUtf8Font :: String -> X FontSet
initUtf8Font s = do
d <- asks display
- (_,_,fs) <- io $ catch (getIt d) (fallBack d)
+ (_,_,fs) <- io $ E.catch (getIt d) (fallBack d)
return fs
where getIt d = createFontSet d s
fallBack d = econst $ createFontSet d "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
diff --git a/XMonad/Util/Loggers.hs b/XMonad/Util/Loggers.hs
index 19e6eae..36f91d9 100644
--- a/XMonad/Util/Loggers.hs
+++ b/XMonad/Util/Loggers.hs
@@ -52,9 +52,8 @@ import XMonad.Hooks.DynamicLog
import XMonad.Util.Font (Align (..))
import XMonad.Util.NamedWindows (getName)
-import Prelude hiding (catch)
import Control.Applicative ((<$>))
-import Control.Exception
+import Control.Exception as E
import Data.List (isPrefixOf, isSuffixOf)
import Data.Maybe (fromMaybe)
import Data.Traversable (traverse)
@@ -143,7 +142,7 @@ loadAvg = logCmd "/usr/bin/uptime | sed 's/.*: //; s/,//g'"
-- | Create a 'Logger' from an arbitrary shell command.
logCmd :: String -> Logger
logCmd c = io $ do (_, out, _, _) <- runInteractiveCommand c
- fmap Just (hGetLine out) `catch` econst Nothing
+ fmap Just (hGetLine out) `E.catch` econst Nothing
-- no need to waitForProcess, we ignore SIGCHLD
-- | Get a count of filtered files in a directory.
diff --git a/XMonad/Util/NamedWindows.hs b/XMonad/Util/NamedWindows.hs
index 653eb54..61176d5 100644
--- a/XMonad/Util/NamedWindows.hs
+++ b/XMonad/Util/NamedWindows.hs
@@ -22,9 +22,8 @@ module XMonad.Util.NamedWindows (
unName
) where
-import Prelude hiding ( catch )
import Control.Applicative ( (<$>) )
-import Control.Exception.Extensible ( bracket, catch, SomeException(..) )
+import Control.Exception.Extensible as E
import Data.Maybe ( fromMaybe, listToMaybe )
import qualified XMonad.StackSet as W ( peek )
@@ -50,11 +49,11 @@ getName w = withDisplay $ \d -> do
let getIt = bracket getProp (xFree . tp_value) (fmap (`NW` w) . copy)
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
copy prop = fromMaybe "" . listToMaybe <$> wcTextPropertyToTextList d prop
- io $ getIt `catch` \(SomeException _) -> ((`NW` w) . resName) `fmap` getClassHint d w
+ io $ getIt `E.catch` \(SomeException _) -> ((`NW` w) . resName) `fmap` getClassHint d w
unName :: NamedWindow -> Window
unName (NW _ w) = w