From 39f010d82d0292d9417a06abaf91dabb43ea3ef4 Mon Sep 17 00:00:00 2001 From: Daniel Wagner Date: Sun, 31 Jul 2011 19:08:50 +0200 Subject: GHC 7 compat Ignore-this: 17a43a709e70ebccc925e016d7057399 * true error: more modules export foldl/foldl'/foldr, so explicitly use the Data.Foldable one * -Werror error: transition from Control.OldException to Control.Exception, assuming everything was IOException darcs-hash:20110731170850-76d51-71271524485f6d10f84521f271182bea5085d400.gz --- XMonad/Hooks/XPropManage.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) (limited to 'XMonad/Hooks/XPropManage.hs') diff --git a/XMonad/Hooks/XPropManage.hs b/XMonad/Hooks/XPropManage.hs index e623aa8..8c2af48 100644 --- a/XMonad/Hooks/XPropManage.hs +++ b/XMonad/Hooks/XPropManage.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE ScopedTypeVariables #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Hooks.XPropManage @@ -17,6 +18,8 @@ module XMonad.Hooks.XPropManage ( xPropManageHook, XPropMatch, pmX, pmP ) where +import Prelude hiding (catch) +import Control.Exception import Data.Char (chr) import Data.Monoid (mconcat, Endo(..)) @@ -73,7 +76,7 @@ xPropManageHook tms = mconcat $ map propToHook tms getProp :: Display -> Window -> Atom -> X ([String]) getProp d w p = do - prop <- io $ catch (getTextProperty d w p >>= wcTextPropertyToTextList d) (\_ -> return [[]]) + prop <- io $ catch (getTextProperty d w p >>= wcTextPropertyToTextList d) (\(_ :: IOException) -> return [[]]) let filt q | q == wM_COMMAND = concat . map splitAtNull | otherwise = id return (filt p prop) -- cgit v1.2.3