mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-01 12:41:52 -07:00
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:
@@ -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
|
||||
|
||||
|
@@ -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
|
||||
|
@@ -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)
|
||||
|
@@ -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 ()
|
||||
|
@@ -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 []
|
||||
|
@@ -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)
|
||||
|
@@ -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
|
||||
|
@@ -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"
|
||||
|
@@ -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
|
||||
|
@@ -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.
|
||||
|
Reference in New Issue
Block a user