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/Actions/GroupNavigation.hs | 12 ++++++------ XMonad/Actions/TagWindows.hs | 7 ++++++- XMonad/Hooks/XPropManage.hs | 5 ++++- XMonad/Layout/WorkspaceDir.hs | 7 ++++++- XMonad/Prompt/DirExec.hs | 8 ++++++-- XMonad/Prompt/RunOrRaise.hs | 7 ++++++- XMonad/Prompt/Shell.hs | 9 +++++++-- XMonad/Prompt/Ssh.hs | 8 +++++++- XMonad/Util/Font.hs | 9 +++++++-- XMonad/Util/Loggers.hs | 7 ++++++- 10 files changed, 61 insertions(+), 18 deletions(-) diff --git a/XMonad/Actions/GroupNavigation.hs b/XMonad/Actions/GroupNavigation.hs index f478e95..910e8ed 100644 --- a/XMonad/Actions/GroupNavigation.hs +++ b/XMonad/Actions/GroupNavigation.hs @@ -30,12 +30,12 @@ module XMonad.Actions.GroupNavigation ( -- * Usage ) where import Control.Monad.Reader -import Data.Foldable +import Data.Foldable as Fold import Data.Map as Map import Data.Sequence as Seq import Data.Set as Set import Graphics.X11.Types -import Prelude hiding (concatMap, drop, elem, filter, foldl, foldr, null, reverse) +import Prelude hiding (concatMap, drop, elem, filter, null, reverse) import XMonad.Core import XMonad.ManageHook import XMonad.Operations (windows, withFocused) @@ -127,7 +127,7 @@ orderedWindowList dir = withWindowSet $ \ss -> do wsids <- asks (Seq.fromList . workspaces . config) let wspcs = orderedWorkspaceList ss wsids wins = dirfun dir - $ foldl' (><) Seq.empty + $ Fold.foldl' (><) Seq.empty $ fmap (Seq.fromList . SS.integrate' . SS.stack) wspcs cur = currentWindow ss return $ maybe wins (rotfun wins) cur @@ -146,7 +146,7 @@ orderedWorkspaceList :: WindowSet -> Seq String -> Seq WindowSpace orderedWorkspaceList ss wsids = rotateTo isCurWS wspcs' where wspcs = SS.workspaces ss - wspcsMap = foldl' (\m ws -> Map.insert (SS.tag ws) ws m) Map.empty wspcs + wspcsMap = Fold.foldl' (\m ws -> Map.insert (SS.tag ws) ws m) Map.empty wspcs wspcs' = fmap (\wsid -> wspcsMap ! wsid) wsids isCurWS ws = SS.tag ws == SS.tag (SS.workspace $ SS.current ss) @@ -184,12 +184,12 @@ updateHistory (HistoryDB oldcur oldhist) = withWindowSet $ \ss -> do --- with Seq.filter and Seq.breakl. flt :: (a -> Bool) -> Seq a -> Seq a -flt p = foldl (\xs x -> if p x then xs |> x else xs) Seq.empty +flt p = Fold.foldl (\xs x -> if p x then xs |> x else xs) Seq.empty brkl :: (a -> Bool) -> Seq a -> (Seq a, Seq a) brkl p xs = flip Seq.splitAt xs $ snd - $ foldr (\x (i, j) -> if p x then (i-1, i-1) else (i-1, j)) (l, l) xs + $ Fold.foldr (\x (i, j) -> if p x then (i-1, i-1) else (i-1, j)) (l, l) xs where l = Seq.length xs diff --git a/XMonad/Actions/TagWindows.hs b/XMonad/Actions/TagWindows.hs index d972aa4..a300f88 100644 --- a/XMonad/Actions/TagWindows.hs +++ b/XMonad/Actions/TagWindows.hs @@ -25,14 +25,19 @@ module XMonad.Actions.TagWindows ( tagDelPrompt ) where +import Prelude hiding (catch) import Data.List (nub,sortBy) import Control.Monad +import Control.Exception import XMonad.StackSet hiding (filter) import XMonad.Prompt import XMonad hiding (workspaces) +econst :: Monad m => a -> IOException -> m a +econst = const . return + -- $usage -- -- To use window tags, import this module into your @~\/.xmonad\/xmonad.hs@: @@ -79,7 +84,7 @@ getTags w = withDisplay $ \d -> io $ catch (internAtom d "_XMONAD_TAGS" False >>= getTextProperty d w >>= wcTextPropertyToTextList d) - (\_ -> return [[]]) + (econst [[]]) >>= return . words . unwords -- | check a window for the given tag 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) diff --git a/XMonad/Layout/WorkspaceDir.hs b/XMonad/Layout/WorkspaceDir.hs index 775653b..ffffded 100644 --- a/XMonad/Layout/WorkspaceDir.hs +++ b/XMonad/Layout/WorkspaceDir.hs @@ -28,6 +28,8 @@ module XMonad.Layout.WorkspaceDir ( changeDir ) where +import Prelude hiding (catch) +import Control.Exception import System.Directory ( setCurrentDirectory, getCurrentDirectory ) import Control.Monad ( when ) @@ -38,6 +40,9 @@ import XMonad.Prompt.Directory ( directoryPrompt ) import XMonad.Layout.LayoutModifier import XMonad.StackSet ( tag, currentTag ) +econst :: Monad m => a -> IOException -> m a +econst = const . return + -- $usage -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: -- @@ -84,7 +89,7 @@ cleanDir :: String -> X String cleanDir x = scd x >> io getCurrentDirectory scd :: String -> X () -scd x = do x' <- io (runProcessWithInput "bash" [] ("echo -n " ++ x) `catch` \_ -> return x) +scd x = do x' <- io (runProcessWithInput "bash" [] ("echo -n " ++ x) `catch` econst x) catchIO $ setCurrentDirectory x' changeDir :: XPConfig -> X () diff --git a/XMonad/Prompt/DirExec.hs b/XMonad/Prompt/DirExec.hs index 035f9b1..1600f93 100644 --- a/XMonad/Prompt/DirExec.hs +++ b/XMonad/Prompt/DirExec.hs @@ -23,12 +23,17 @@ module XMonad.Prompt.DirExec , dirExecPromptNamed ) where +import Prelude hiding (catch) +import Control.Exception import System.Directory import Control.Monad import Data.List import XMonad import XMonad.Prompt +econst :: Monad m => a -> IOException -> m a +econst = const . return + -- $usage -- 1. In your @~\/.xmonad\/xmonad.hs@: -- @@ -98,5 +103,4 @@ getDirectoryExecutables path = liftM2 (&&) (doesFileExist x') (liftM executable (getPermissions x')))) - `catch` (return . return . show) - + `catch` econst [] diff --git a/XMonad/Prompt/RunOrRaise.hs b/XMonad/Prompt/RunOrRaise.hs index 5fcfb3a..251e09c 100644 --- a/XMonad/Prompt/RunOrRaise.hs +++ b/XMonad/Prompt/RunOrRaise.hs @@ -25,9 +25,14 @@ import XMonad.Prompt.Shell import XMonad.Actions.WindowGo (runOrRaise) import XMonad.Util.Run (runProcessWithInput) +import Prelude hiding (catch) +import Control.Exception import Control.Monad (liftM, liftM2) import System.Directory (doesDirectoryExist, doesFileExist, executable, getPermissions) +econst :: Monad m => a -> IOException -> m a +econst = const . return + {- $usage 1. In your @~\/.xmonad\/xmonad.hs@: @@ -65,7 +70,7 @@ isApp "thunderbird" = className =? "Thunderbird-bin" <||> className =? "Thunderb isApp x = liftM2 (==) pid $ pidof x pidof :: String -> Query Int -pidof x = io $ (runProcessWithInput "pidof" [x] [] >>= readIO) `catch` (\_ -> return 0) +pidof x = io $ (runProcessWithInput "pidof" [x] [] >>= readIO) `catch` econst 0 pid :: Query Int pid = ask >>= (\w -> liftX $ withDisplay $ \d -> getPID d w) diff --git a/XMonad/Prompt/Shell.hs b/XMonad/Prompt/Shell.hs index a8ddff4..9ed9293 100644 --- a/XMonad/Prompt/Shell.hs +++ b/XMonad/Prompt/Shell.hs @@ -25,8 +25,10 @@ module XMonad.Prompt.Shell ) where import Codec.Binary.UTF8.String (decodeString, encodeString) +import Control.Exception import Control.Monad (forM) import Data.List (isPrefixOf) +import Prelude hiding (catch) import System.Directory (doesDirectoryExist, getDirectoryContents) import System.Environment (getEnv) import System.Posix.Files (getFileStatus, isDirectory) @@ -35,6 +37,9 @@ import XMonad.Util.Run import XMonad hiding (config) import XMonad.Prompt +econst :: Monad m => a -> IOException -> m a +econst = const . return + {- $usage 1. In your @~\/.xmonad\/xmonad.hs@: @@ -97,7 +102,7 @@ commandCompletionFunction cmds str | '/' `elem` str = [] getCommands :: IO [String] getCommands = do - p <- getEnv "PATH" `catch` const (return []) + p <- getEnv "PATH" `catch` econst [] let ds = filter (/= "") $ split ':' p es <- forM ds $ \d -> do exists <- doesDirectoryExist d @@ -126,7 +131,7 @@ isSpecialChar = flip elem " &\\@\"'#?$*()[]{};" -- | Ask the shell environment for env :: String -> String -> IO String -env variable fallthrough = getEnv variable `catch` \_ -> return fallthrough +env variable fallthrough = getEnv variable `catch` econst fallthrough {- | Ask the shell what browser the user likes. If the user hasn't defined any $BROWSER, defaults to returning \"firefox\", since that seems to be the most diff --git a/XMonad/Prompt/Ssh.hs b/XMonad/Prompt/Ssh.hs index 122c137..7d84069 100644 --- a/XMonad/Prompt/Ssh.hs +++ b/XMonad/Prompt/Ssh.hs @@ -18,16 +18,22 @@ module XMonad.Prompt.Ssh sshPrompt ) where +import Prelude hiding (catch) + import XMonad import XMonad.Util.Run import XMonad.Prompt import System.Directory import System.Environment +import Control.Exception import Control.Monad import Data.Maybe +econst :: Monad m => a -> IOException -> m a +econst = const . return + -- $usage -- 1. In your @~\/.xmonad\/xmonad.hs@: -- @@ -71,7 +77,7 @@ sshComplListLocal = do sshComplListGlobal :: IO [String] sshComplListGlobal = do - env <- getEnv "SSH_KNOWN_HOSTS" `catch` (\_ -> return "/nonexistent") + env <- getEnv "SSH_KNOWN_HOSTS" `catch` econst "/nonexistent" fs <- mapM fileExists [ env , "/usr/local/etc/ssh/ssh_known_hosts" , "/usr/local/etc/ssh_known_hosts" 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. -- cgit v1.2.3