GHC 7 compat

* 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
This commit is contained in:
Daniel Wagner
2011-07-31 17:08:50 +00:00
parent 1364a00c84
commit 2443a962a0
10 changed files with 61 additions and 18 deletions

View File

@@ -30,12 +30,12 @@ module XMonad.Actions.GroupNavigation ( -- * Usage
) where ) where
import Control.Monad.Reader import Control.Monad.Reader
import Data.Foldable import Data.Foldable as Fold
import Data.Map as Map import Data.Map as Map
import Data.Sequence as Seq import Data.Sequence as Seq
import Data.Set as Set import Data.Set as Set
import Graphics.X11.Types 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.Core
import XMonad.ManageHook import XMonad.ManageHook
import XMonad.Operations (windows, withFocused) import XMonad.Operations (windows, withFocused)
@@ -127,7 +127,7 @@ orderedWindowList dir = withWindowSet $ \ss -> do
wsids <- asks (Seq.fromList . workspaces . config) wsids <- asks (Seq.fromList . workspaces . config)
let wspcs = orderedWorkspaceList ss wsids let wspcs = orderedWorkspaceList ss wsids
wins = dirfun dir wins = dirfun dir
$ foldl' (><) Seq.empty $ Fold.foldl' (><) Seq.empty
$ fmap (Seq.fromList . SS.integrate' . SS.stack) wspcs $ fmap (Seq.fromList . SS.integrate' . SS.stack) wspcs
cur = currentWindow ss cur = currentWindow ss
return $ maybe wins (rotfun wins) cur return $ maybe wins (rotfun wins) cur
@@ -146,7 +146,7 @@ orderedWorkspaceList :: WindowSet -> Seq String -> Seq WindowSpace
orderedWorkspaceList ss wsids = rotateTo isCurWS wspcs' orderedWorkspaceList ss wsids = rotateTo isCurWS wspcs'
where where
wspcs = SS.workspaces ss 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 wspcs' = fmap (\wsid -> wspcsMap ! wsid) wsids
isCurWS ws = SS.tag ws == SS.tag (SS.workspace $ SS.current ss) 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. --- with Seq.filter and Seq.breakl.
flt :: (a -> Bool) -> Seq a -> Seq a 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 :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
brkl p xs = flip Seq.splitAt xs brkl p xs = flip Seq.splitAt xs
$ snd $ 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 where
l = Seq.length xs l = Seq.length xs

View File

@@ -25,14 +25,19 @@ module XMonad.Actions.TagWindows (
tagDelPrompt tagDelPrompt
) where ) where
import Prelude hiding (catch)
import Data.List (nub,sortBy) import Data.List (nub,sortBy)
import Control.Monad import Control.Monad
import Control.Exception
import XMonad.StackSet hiding (filter) import XMonad.StackSet hiding (filter)
import XMonad.Prompt import XMonad.Prompt
import XMonad hiding (workspaces) import XMonad hiding (workspaces)
econst :: Monad m => a -> IOException -> m a
econst = const . return
-- $usage -- $usage
-- --
-- To use window tags, import this module into your @~\/.xmonad\/xmonad.hs@: -- 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 >>= io $ catch (internAtom d "_XMONAD_TAGS" False >>=
getTextProperty d w >>= getTextProperty d w >>=
wcTextPropertyToTextList d) wcTextPropertyToTextList d)
(\_ -> return [[]]) (econst [[]])
>>= return . words . unwords >>= return . words . unwords
-- | check a window for the given tag -- | check a window for the given tag

View File

@@ -1,3 +1,4 @@
{-# LANGUAGE ScopedTypeVariables #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Hooks.XPropManage -- Module : XMonad.Hooks.XPropManage
@@ -17,6 +18,8 @@ module XMonad.Hooks.XPropManage (
xPropManageHook, XPropMatch, pmX, pmP xPropManageHook, XPropMatch, pmX, pmP
) where ) where
import Prelude hiding (catch)
import Control.Exception
import Data.Char (chr) import Data.Char (chr)
import Data.Monoid (mconcat, Endo(..)) import Data.Monoid (mconcat, Endo(..))
@@ -73,7 +76,7 @@ xPropManageHook tms = mconcat $ map propToHook tms
getProp :: Display -> Window -> Atom -> X ([String]) getProp :: Display -> Window -> Atom -> X ([String])
getProp d w p = do 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 let filt q | q == wM_COMMAND = concat . map splitAtNull
| otherwise = id | otherwise = id
return (filt p prop) return (filt p prop)

View File

@@ -28,6 +28,8 @@ module XMonad.Layout.WorkspaceDir (
changeDir changeDir
) where ) where
import Prelude hiding (catch)
import Control.Exception
import System.Directory ( setCurrentDirectory, getCurrentDirectory ) import System.Directory ( setCurrentDirectory, getCurrentDirectory )
import Control.Monad ( when ) import Control.Monad ( when )
@@ -38,6 +40,9 @@ import XMonad.Prompt.Directory ( directoryPrompt )
import XMonad.Layout.LayoutModifier import XMonad.Layout.LayoutModifier
import XMonad.StackSet ( tag, currentTag ) import XMonad.StackSet ( tag, currentTag )
econst :: Monad m => a -> IOException -> m a
econst = const . return
-- $usage -- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: -- 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 cleanDir x = scd x >> io getCurrentDirectory
scd :: String -> X () 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' catchIO $ setCurrentDirectory x'
changeDir :: XPConfig -> X () changeDir :: XPConfig -> X ()

View File

@@ -23,12 +23,17 @@ module XMonad.Prompt.DirExec
, dirExecPromptNamed , dirExecPromptNamed
) where ) where
import Prelude hiding (catch)
import Control.Exception
import System.Directory import System.Directory
import Control.Monad import Control.Monad
import Data.List import Data.List
import XMonad import XMonad
import XMonad.Prompt import XMonad.Prompt
econst :: Monad m => a -> IOException -> m a
econst = const . return
-- $usage -- $usage
-- 1. In your @~\/.xmonad\/xmonad.hs@: -- 1. In your @~\/.xmonad\/xmonad.hs@:
-- --
@@ -98,5 +103,4 @@ getDirectoryExecutables path =
liftM2 (&&) liftM2 (&&)
(doesFileExist x') (doesFileExist x')
(liftM executable (getPermissions x')))) (liftM executable (getPermissions x'))))
`catch` (return . return . show) `catch` econst []

View File

@@ -25,9 +25,14 @@ import XMonad.Prompt.Shell
import XMonad.Actions.WindowGo (runOrRaise) import XMonad.Actions.WindowGo (runOrRaise)
import XMonad.Util.Run (runProcessWithInput) import XMonad.Util.Run (runProcessWithInput)
import Prelude hiding (catch)
import Control.Exception
import Control.Monad (liftM, liftM2) import Control.Monad (liftM, liftM2)
import System.Directory (doesDirectoryExist, doesFileExist, executable, getPermissions) import System.Directory (doesDirectoryExist, doesFileExist, executable, getPermissions)
econst :: Monad m => a -> IOException -> m a
econst = const . return
{- $usage {- $usage
1. In your @~\/.xmonad\/xmonad.hs@: 1. In your @~\/.xmonad\/xmonad.hs@:
@@ -65,7 +70,7 @@ isApp "thunderbird" = className =? "Thunderbird-bin" <||> className =? "Thunderb
isApp x = liftM2 (==) pid $ pidof x isApp x = liftM2 (==) pid $ pidof x
pidof :: String -> Query Int 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 :: Query Int
pid = ask >>= (\w -> liftX $ withDisplay $ \d -> getPID d w) pid = ask >>= (\w -> liftX $ withDisplay $ \d -> getPID d w)

View File

@@ -25,8 +25,10 @@ module XMonad.Prompt.Shell
) where ) where
import Codec.Binary.UTF8.String (decodeString, encodeString) import Codec.Binary.UTF8.String (decodeString, encodeString)
import Control.Exception
import Control.Monad (forM) import Control.Monad (forM)
import Data.List (isPrefixOf) import Data.List (isPrefixOf)
import Prelude hiding (catch)
import System.Directory (doesDirectoryExist, getDirectoryContents) import System.Directory (doesDirectoryExist, getDirectoryContents)
import System.Environment (getEnv) import System.Environment (getEnv)
import System.Posix.Files (getFileStatus, isDirectory) import System.Posix.Files (getFileStatus, isDirectory)
@@ -35,6 +37,9 @@ import XMonad.Util.Run
import XMonad hiding (config) import XMonad hiding (config)
import XMonad.Prompt import XMonad.Prompt
econst :: Monad m => a -> IOException -> m a
econst = const . return
{- $usage {- $usage
1. In your @~\/.xmonad\/xmonad.hs@: 1. In your @~\/.xmonad\/xmonad.hs@:
@@ -97,7 +102,7 @@ commandCompletionFunction cmds str | '/' `elem` str = []
getCommands :: IO [String] getCommands :: IO [String]
getCommands = do getCommands = do
p <- getEnv "PATH" `catch` const (return []) p <- getEnv "PATH" `catch` econst []
let ds = filter (/= "") $ split ':' p let ds = filter (/= "") $ split ':' p
es <- forM ds $ \d -> do es <- forM ds $ \d -> do
exists <- doesDirectoryExist d exists <- doesDirectoryExist d
@@ -126,7 +131,7 @@ isSpecialChar = flip elem " &\\@\"'#?$*()[]{};"
-- | Ask the shell environment for -- | Ask the shell environment for
env :: String -> String -> IO String 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 {- | 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 $BROWSER, defaults to returning \"firefox\", since that seems to be the most

View File

@@ -18,16 +18,22 @@ module XMonad.Prompt.Ssh
sshPrompt sshPrompt
) where ) where
import Prelude hiding (catch)
import XMonad import XMonad
import XMonad.Util.Run import XMonad.Util.Run
import XMonad.Prompt import XMonad.Prompt
import System.Directory import System.Directory
import System.Environment import System.Environment
import Control.Exception
import Control.Monad import Control.Monad
import Data.Maybe import Data.Maybe
econst :: Monad m => a -> IOException -> m a
econst = const . return
-- $usage -- $usage
-- 1. In your @~\/.xmonad\/xmonad.hs@: -- 1. In your @~\/.xmonad\/xmonad.hs@:
-- --
@@ -71,7 +77,7 @@ sshComplListLocal = do
sshComplListGlobal :: IO [String] sshComplListGlobal :: IO [String]
sshComplListGlobal = do sshComplListGlobal = do
env <- getEnv "SSH_KNOWN_HOSTS" `catch` (\_ -> return "/nonexistent") env <- getEnv "SSH_KNOWN_HOSTS" `catch` econst "/nonexistent"
fs <- mapM fileExists [ env fs <- mapM fileExists [ env
, "/usr/local/etc/ssh/ssh_known_hosts" , "/usr/local/etc/ssh/ssh_known_hosts"
, "/usr/local/etc/ssh_known_hosts" , "/usr/local/etc/ssh_known_hosts"

View File

@@ -32,9 +32,11 @@ module XMonad.Util.Font
, fi , fi
) where ) where
import Prelude hiding (catch)
import XMonad import XMonad
import Foreign import Foreign
import Control.Applicative import Control.Applicative
import Control.Exception
import Data.Maybe import Data.Maybe
#ifdef XFT #ifdef XFT
@@ -60,6 +62,9 @@ stringToPixel d s = fromMaybe fallBack <$> io getIt
where getIt = initColor d s where getIt = initColor d s
fallBack = blackPixel d (defaultScreen d) fallBack = blackPixel d (defaultScreen d)
econst :: a -> IOException -> a
econst = const
-- | Given a fontname returns the font structure. If the font name is -- | Given a fontname returns the font structure. If the font name is
-- not valid the default font will be loaded and returned. -- not valid the default font will be loaded and returned.
initCoreFont :: String -> X FontStruct initCoreFont :: String -> X FontStruct
@@ -67,7 +72,7 @@ initCoreFont s = do
d <- asks display d <- asks display
io $ catch (getIt d) (fallBack d) io $ catch (getIt d) (fallBack d)
where getIt d = loadQueryFont d s 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 :: FontStruct -> X ()
releaseCoreFont fs = do releaseCoreFont fs = do
@@ -80,7 +85,7 @@ initUtf8Font s = do
(_,_,fs) <- io $ catch (getIt d) (fallBack d) (_,_,fs) <- io $ catch (getIt d) (fallBack d)
return fs return fs
where getIt d = createFontSet d s 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 :: FontSet -> X ()
releaseUtf8Font fs = do releaseUtf8Font fs = do

View File

@@ -52,7 +52,9 @@ import XMonad.Hooks.DynamicLog
import XMonad.Util.Font (Align (..)) import XMonad.Util.Font (Align (..))
import XMonad.Util.NamedWindows (getName) import XMonad.Util.NamedWindows (getName)
import Prelude hiding (catch)
import Control.Applicative ((<$>)) import Control.Applicative ((<$>))
import Control.Exception
import Data.List (isPrefixOf, isSuffixOf) import Data.List (isPrefixOf, isSuffixOf)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.Traversable (traverse) import Data.Traversable (traverse)
@@ -62,6 +64,9 @@ import System.Locale
import System.Process (runInteractiveCommand) import System.Process (runInteractiveCommand)
import System.Time import System.Time
econst :: Monad m => a -> IOException -> m a
econst = const . return
-- $usage -- $usage
-- Use this module by importing it into your @~\/.xmonad\/xmonad.hs@: -- 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. -- | Create a 'Logger' from an arbitrary shell command.
logCmd :: String -> Logger logCmd :: String -> Logger
logCmd c = io $ do (_, out, _, _) <- runInteractiveCommand c 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 -- no need to waitForProcess, we ignore SIGCHLD
-- | Get a count of filtered files in a directory. -- | Get a count of filtered files in a directory.