aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Util')
-rw-r--r--XMonad/Util/Font.hs9
-rw-r--r--XMonad/Util/Loggers.hs7
2 files changed, 13 insertions, 3 deletions
diff --git a/XMonad/Util/Font.hs b/XMonad/Util/Font.hs
index d05b433..ed09a6d 100644
--- a/XMonad/Util/Font.hs
+++ b/XMonad/Util/Font.hs
@@ -32,9 +32,11 @@ module XMonad.Util.Font
, fi
) where
+import Prelude hiding (catch)
import XMonad
import Foreign
import Control.Applicative
+import Control.Exception
import Data.Maybe
#ifdef XFT
@@ -60,6 +62,9 @@ stringToPixel d s = fromMaybe fallBack <$> io getIt
where getIt = initColor d s
fallBack = blackPixel d (defaultScreen d)
+econst :: a -> IOException -> a
+econst = const
+
-- | Given a fontname returns the font structure. If the font name is
-- not valid the default font will be loaded and returned.
initCoreFont :: String -> X FontStruct
@@ -67,7 +72,7 @@ initCoreFont s = do
d <- asks display
io $ catch (getIt d) (fallBack d)
where getIt d = loadQueryFont d s
- fallBack d = const $ loadQueryFont d "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
+ fallBack d = econst $ loadQueryFont d "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
releaseCoreFont :: FontStruct -> X ()
releaseCoreFont fs = do
@@ -80,7 +85,7 @@ initUtf8Font s = do
(_,_,fs) <- io $ catch (getIt d) (fallBack d)
return fs
where getIt d = createFontSet d s
- fallBack d = const $ createFontSet d "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
+ fallBack d = econst $ createFontSet d "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
releaseUtf8Font :: FontSet -> X ()
releaseUtf8Font fs = do
diff --git a/XMonad/Util/Loggers.hs b/XMonad/Util/Loggers.hs
index 3c8c3ee..19e6eae 100644
--- a/XMonad/Util/Loggers.hs
+++ b/XMonad/Util/Loggers.hs
@@ -52,7 +52,9 @@ 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 Data.List (isPrefixOf, isSuffixOf)
import Data.Maybe (fromMaybe)
import Data.Traversable (traverse)
@@ -62,6 +64,9 @@ import System.Locale
import System.Process (runInteractiveCommand)
import System.Time
+econst :: Monad m => a -> IOException -> m a
+econst = const . return
+
-- $usage
-- Use this module by importing it into your @~\/.xmonad\/xmonad.hs@:
--
@@ -138,7 +143,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` (const $ return Nothing)
+ fmap Just (hGetLine out) `catch` econst Nothing
-- no need to waitForProcess, we ignore SIGCHLD
-- | Get a count of filtered files in a directory.