mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-05 06:31:53 -07:00
Use Control.Exception.catch explitly to avoid warnings
The base that comes with ghc-7.6.1 no longer includes Prelude.catch; so these modules were changed so that there is no warning for import Prelude hiding (catch) At the same time these changes should be compatible with older GHCs, since the catch being has never been the one in the Prelude.
This commit is contained in:
@@ -26,10 +26,9 @@ module XMonad.Actions.TagWindows (
|
|||||||
TagPrompt,
|
TagPrompt,
|
||||||
) 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 Control.Exception as E
|
||||||
|
|
||||||
import XMonad.StackSet hiding (filter)
|
import XMonad.StackSet hiding (filter)
|
||||||
|
|
||||||
@@ -82,7 +81,7 @@ setTag s w = withDisplay $ \d ->
|
|||||||
-- reads from the \"_XMONAD_TAGS\" window property
|
-- reads from the \"_XMONAD_TAGS\" window property
|
||||||
getTags :: Window -> X [String]
|
getTags :: Window -> X [String]
|
||||||
getTags w = withDisplay $ \d ->
|
getTags w = withDisplay $ \d ->
|
||||||
io $ catch (internAtom d "_XMONAD_TAGS" False >>=
|
io $ E.catch (internAtom d "_XMONAD_TAGS" False >>=
|
||||||
getTextProperty d w >>=
|
getTextProperty d w >>=
|
||||||
wcTextPropertyToTextList d)
|
wcTextPropertyToTextList d)
|
||||||
(econst [[]])
|
(econst [[]])
|
||||||
|
@@ -18,8 +18,7 @@ module XMonad.Hooks.XPropManage (
|
|||||||
xPropManageHook, XPropMatch, pmX, pmP
|
xPropManageHook, XPropMatch, pmX, pmP
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Prelude hiding (catch)
|
import Control.Exception as E
|
||||||
import Control.Exception
|
|
||||||
import Data.Char (chr)
|
import Data.Char (chr)
|
||||||
import Data.Monoid (mconcat, Endo(..))
|
import Data.Monoid (mconcat, Endo(..))
|
||||||
|
|
||||||
@@ -76,7 +75,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) (\(_ :: IOException) -> return [[]])
|
prop <- io $ E.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)
|
||||||
|
@@ -29,7 +29,6 @@ module XMonad.Layout.WorkspaceDir (
|
|||||||
WorkspaceDir,
|
WorkspaceDir,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Prelude hiding (catch)
|
|
||||||
import System.Directory ( setCurrentDirectory, getCurrentDirectory )
|
import System.Directory ( setCurrentDirectory, getCurrentDirectory )
|
||||||
import Control.Monad ( when )
|
import Control.Monad ( when )
|
||||||
|
|
||||||
|
@@ -68,8 +68,6 @@ module XMonad.Prompt
|
|||||||
, XPState
|
, XPState
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Prelude hiding (catch)
|
|
||||||
|
|
||||||
import XMonad hiding (cleanMask, config)
|
import XMonad hiding (cleanMask, config)
|
||||||
import qualified XMonad as X (numberlockMask)
|
import qualified XMonad as X (numberlockMask)
|
||||||
import qualified XMonad.StackSet as W
|
import qualified XMonad.StackSet as W
|
||||||
@@ -81,7 +79,7 @@ import Codec.Binary.UTF8.String (decodeString)
|
|||||||
import Control.Applicative ((<$>))
|
import Control.Applicative ((<$>))
|
||||||
import Control.Arrow (first, (&&&), (***))
|
import Control.Arrow (first, (&&&), (***))
|
||||||
import Control.Concurrent (threadDelay)
|
import Control.Concurrent (threadDelay)
|
||||||
import Control.Exception.Extensible hiding (handle)
|
import Control.Exception.Extensible as E hiding (handle)
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
import Data.Bits
|
import Data.Bits
|
||||||
import Data.Char (isSpace)
|
import Data.Char (isSpace)
|
||||||
@@ -890,7 +888,7 @@ getCompletions :: XP [String]
|
|||||||
getCompletions = do
|
getCompletions = do
|
||||||
s <- get
|
s <- get
|
||||||
io $ getCompletionFunction s (commandToComplete (currentXPMode s) (command s))
|
io $ getCompletionFunction s (commandToComplete (currentXPMode s) (command s))
|
||||||
`catch` \(SomeException _) -> return []
|
`E.catch` \(SomeException _) -> return []
|
||||||
|
|
||||||
setComplWin :: Window -> ComplWindowDim -> XP ()
|
setComplWin :: Window -> ComplWindowDim -> XP ()
|
||||||
setComplWin w wi =
|
setComplWin w wi =
|
||||||
@@ -1028,7 +1026,7 @@ getHistoryFile :: IO FilePath
|
|||||||
getHistoryFile = fmap (++ "/history") $ getAppUserDataDirectory "xmonad"
|
getHistoryFile = fmap (++ "/history") $ getAppUserDataDirectory "xmonad"
|
||||||
|
|
||||||
readHistory :: IO History
|
readHistory :: IO History
|
||||||
readHistory = readHist `catch` \(SomeException _) -> return emptyHistory
|
readHistory = readHist `E.catch` \(SomeException _) -> return emptyHistory
|
||||||
where
|
where
|
||||||
readHist = do
|
readHist = do
|
||||||
path <- getHistoryFile
|
path <- getHistoryFile
|
||||||
@@ -1039,7 +1037,7 @@ writeHistory :: History -> IO ()
|
|||||||
writeHistory hist = do
|
writeHistory hist = do
|
||||||
path <- getHistoryFile
|
path <- getHistoryFile
|
||||||
let filtered = M.filter (not . null) hist
|
let filtered = M.filter (not . null) hist
|
||||||
writeFile path (show filtered) `catch` \(SomeException e) ->
|
writeFile path (show filtered) `E.catch` \(SomeException e) ->
|
||||||
hPutStrLn stderr ("error writing history: "++show e)
|
hPutStrLn stderr ("error writing history: "++show e)
|
||||||
setFileMode path mode
|
setFileMode path mode
|
||||||
where mode = ownerReadMode .|. ownerWriteMode
|
where mode = ownerReadMode .|. ownerWriteMode
|
||||||
|
@@ -24,8 +24,7 @@ module XMonad.Prompt.DirExec
|
|||||||
, DirExec
|
, DirExec
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Prelude hiding (catch)
|
import Control.Exception as E
|
||||||
import Control.Exception
|
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Data.List
|
import Data.List
|
||||||
@@ -104,4 +103,4 @@ getDirectoryExecutables path =
|
|||||||
liftM2 (&&)
|
liftM2 (&&)
|
||||||
(doesFileExist x')
|
(doesFileExist x')
|
||||||
(liftM executable (getPermissions x'))))
|
(liftM executable (getPermissions x'))))
|
||||||
`catch` econst []
|
`E.catch` econst []
|
||||||
|
@@ -26,8 +26,7 @@ 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 as E
|
||||||
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)
|
||||||
|
|
||||||
@@ -71,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` econst 0
|
pidof x = io $ (runProcessWithInput "pidof" [x] [] >>= readIO) `E.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)
|
||||||
|
@@ -30,10 +30,9 @@ module XMonad.Prompt.Shell
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import Codec.Binary.UTF8.String (encodeString)
|
import Codec.Binary.UTF8.String (encodeString)
|
||||||
import Control.Exception
|
import Control.Exception as E
|
||||||
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)
|
||||||
@@ -111,7 +110,7 @@ commandCompletionFunction cmds str | '/' `elem` str = []
|
|||||||
|
|
||||||
getCommands :: IO [String]
|
getCommands :: IO [String]
|
||||||
getCommands = do
|
getCommands = do
|
||||||
p <- getEnv "PATH" `catch` econst []
|
p <- getEnv "PATH" `E.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
|
||||||
@@ -142,7 +141,7 @@ isSpecialChar = flip elem " &\\@\"'#?$*()[]{};"
|
|||||||
-- In order to /set/ an environment variable (eg. combine with a prompt so you can modify @$HTTP_PROXY@ dynamically),
|
-- In order to /set/ an environment variable (eg. combine with a prompt so you can modify @$HTTP_PROXY@ dynamically),
|
||||||
-- you need to use 'System.Posix.putEnv'.
|
-- you need to use 'System.Posix.putEnv'.
|
||||||
env :: String -> String -> IO String
|
env :: String -> String -> IO String
|
||||||
env variable fallthrough = getEnv variable `catch` econst fallthrough
|
env variable fallthrough = getEnv variable `E.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
|
||||||
|
@@ -19,15 +19,13 @@ module XMonad.Prompt.Ssh
|
|||||||
Ssh,
|
Ssh,
|
||||||
) 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.Exception as E
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
@@ -78,7 +76,7 @@ sshComplListLocal = do
|
|||||||
|
|
||||||
sshComplListGlobal :: IO [String]
|
sshComplListGlobal :: IO [String]
|
||||||
sshComplListGlobal = do
|
sshComplListGlobal = do
|
||||||
env <- getEnv "SSH_KNOWN_HOSTS" `catch` econst "/nonexistent"
|
env <- getEnv "SSH_KNOWN_HOSTS" `E.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"
|
||||||
|
@@ -32,11 +32,10 @@ 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 Control.Exception as E
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
|
|
||||||
#ifdef XFT
|
#ifdef XFT
|
||||||
@@ -70,7 +69,7 @@ econst = const
|
|||||||
initCoreFont :: String -> X FontStruct
|
initCoreFont :: String -> X FontStruct
|
||||||
initCoreFont s = do
|
initCoreFont s = do
|
||||||
d <- asks display
|
d <- asks display
|
||||||
io $ catch (getIt d) (fallBack d)
|
io $ E.catch (getIt d) (fallBack d)
|
||||||
where getIt d = loadQueryFont d s
|
where getIt d = loadQueryFont d s
|
||||||
fallBack d = econst $ loadQueryFont d "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
|
fallBack d = econst $ loadQueryFont d "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
|
||||||
|
|
||||||
@@ -82,7 +81,7 @@ releaseCoreFont fs = do
|
|||||||
initUtf8Font :: String -> X FontSet
|
initUtf8Font :: String -> X FontSet
|
||||||
initUtf8Font s = do
|
initUtf8Font s = do
|
||||||
d <- asks display
|
d <- asks display
|
||||||
(_,_,fs) <- io $ catch (getIt d) (fallBack d)
|
(_,_,fs) <- io $ E.catch (getIt d) (fallBack d)
|
||||||
return fs
|
return fs
|
||||||
where getIt d = createFontSet d s
|
where getIt d = createFontSet d s
|
||||||
fallBack d = econst $ createFontSet d "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
|
fallBack d = econst $ createFontSet d "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
|
||||||
|
@@ -52,9 +52,8 @@ 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 Control.Exception as E
|
||||||
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)
|
||||||
@@ -143,7 +142,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` econst Nothing
|
fmap Just (hGetLine out) `E.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.
|
||||||
|
@@ -22,9 +22,8 @@ module XMonad.Util.NamedWindows (
|
|||||||
unName
|
unName
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Prelude hiding ( catch )
|
|
||||||
import Control.Applicative ( (<$>) )
|
import Control.Applicative ( (<$>) )
|
||||||
import Control.Exception.Extensible ( bracket, catch, SomeException(..) )
|
import Control.Exception.Extensible as E
|
||||||
import Data.Maybe ( fromMaybe, listToMaybe )
|
import Data.Maybe ( fromMaybe, listToMaybe )
|
||||||
|
|
||||||
import qualified XMonad.StackSet as W ( peek )
|
import qualified XMonad.StackSet as W ( peek )
|
||||||
@@ -50,11 +49,11 @@ getName w = withDisplay $ \d -> do
|
|||||||
let getIt = bracket getProp (xFree . tp_value) (fmap (`NW` w) . copy)
|
let getIt = bracket getProp (xFree . tp_value) (fmap (`NW` w) . copy)
|
||||||
|
|
||||||
getProp = (internAtom d "_NET_WM_NAME" False >>= getTextProperty d w)
|
getProp = (internAtom d "_NET_WM_NAME" False >>= getTextProperty d w)
|
||||||
`catch` \(SomeException _) -> getTextProperty d w wM_NAME
|
`E.catch` \(SomeException _) -> getTextProperty d w wM_NAME
|
||||||
|
|
||||||
copy prop = fromMaybe "" . listToMaybe <$> wcTextPropertyToTextList d prop
|
copy prop = fromMaybe "" . listToMaybe <$> wcTextPropertyToTextList d prop
|
||||||
|
|
||||||
io $ getIt `catch` \(SomeException _) -> ((`NW` w) . resName) `fmap` getClassHint d w
|
io $ getIt `E.catch` \(SomeException _) -> ((`NW` w) . resName) `fmap` getClassHint d w
|
||||||
|
|
||||||
unName :: NamedWindow -> Window
|
unName :: NamedWindow -> Window
|
||||||
unName (NW _ w) = w
|
unName (NW _ w) = w
|
||||||
|
Reference in New Issue
Block a user