198 lines
8.9 KiB
Diff
198 lines
8.9 KiB
Diff
|
diff -up xmonad-contrib-0.9.1/XMonad/Layout/HintedGrid.hs~ xmonad-contrib-0.9.1/XMonad/Layout/HintedGrid.hs
|
||
|
--- xmonad-contrib-0.9.1/XMonad/Layout/HintedGrid.hs~ 2009-12-17 09:32:25.000000000 +1000
|
||
|
+++ xmonad-contrib-0.9.1/XMonad/Layout/HintedGrid.hs 2010-11-26 23:56:40.000000000 +1000
|
||
|
@@ -65,7 +65,7 @@ instance LayoutClass Grid Window where
|
||
|
doLayout (GridRatio d m) r w = flip (,) Nothing . arrange d m r (integrate w)
|
||
|
|
||
|
replicateS :: Int -> (a -> (b, a)) -> a -> ([b], a)
|
||
|
-replicateS n = runState . replicateM n . State
|
||
|
+replicateS n f = runState . replicateM n $ do (a,s) <- gets f; put s; return a
|
||
|
|
||
|
doColumn :: Dimension -> Dimension -> Dimension -> [(D -> D)] -> [D]
|
||
|
doColumn width height k adjs =
|
||
|
diff -up xmonad-contrib-0.9.1/XMonad/Prompt.hs~ xmonad-contrib-0.9.1/XMonad/Prompt.hs
|
||
|
--- xmonad-contrib-0.9.1/XMonad/Prompt.hs~ 2009-12-17 09:32:25.000000000 +1000
|
||
|
+++ xmonad-contrib-0.9.1/XMonad/Prompt.hs 2010-11-27 00:07:57.000000000 +1000
|
||
|
@@ -71,6 +71,7 @@ import XMonad.Util.XSelection (getSelect
|
||
|
|
||
|
import Control.Arrow ((&&&),first)
|
||
|
import Control.Concurrent (threadDelay)
|
||
|
+import Control.Exception.Extensible hiding (handle)
|
||
|
import Control.Monad.Reader
|
||
|
import Control.Monad.State
|
||
|
import Control.Applicative ((<$>))
|
||
|
@@ -82,7 +83,6 @@ import Data.Set (fromList, toList)
|
||
|
import System.Directory
|
||
|
import System.IO
|
||
|
import System.Posix.Files
|
||
|
-import Control.Exception hiding (handle)
|
||
|
|
||
|
import qualified Data.Map as M
|
||
|
|
||
|
@@ -627,7 +627,7 @@ getCompletions :: XP [String]
|
||
|
getCompletions = do
|
||
|
s <- get
|
||
|
io $ completionFunction s (commandToComplete (xptype s) (command s))
|
||
|
- `catch` \_ -> return []
|
||
|
+ `catch` \(SomeException _) -> return []
|
||
|
|
||
|
setComplWin :: Window -> ComplWindowDim -> XP ()
|
||
|
setComplWin w wi =
|
||
|
@@ -758,7 +758,7 @@ getHistoryFile :: IO FilePath
|
||
|
getHistoryFile = fmap (++ "/history") $ getAppUserDataDirectory "xmonad"
|
||
|
|
||
|
readHistory :: IO History
|
||
|
-readHistory = catch readHist (const (return emptyHistory))
|
||
|
+readHistory = readHist `catch` \(SomeException _) -> return emptyHistory
|
||
|
where
|
||
|
readHist = do
|
||
|
path <- getHistoryFile
|
||
|
@@ -768,7 +768,9 @@ readHistory = catch readHist (const (ret
|
||
|
writeHistory :: History -> IO ()
|
||
|
writeHistory hist = do
|
||
|
path <- getHistoryFile
|
||
|
- catch (writeFile path (show hist)) $ const $ hPutStrLn stderr "error in writing"
|
||
|
+ let filtered = M.filter (not . null) hist
|
||
|
+ writeFile path (show filtered) `catch` \(SomeException e) ->
|
||
|
+ hPutStrLn stderr ("error writing history: "++show e)
|
||
|
setFileMode path mode
|
||
|
where mode = ownerReadMode .|. ownerWriteMode
|
||
|
|
||
|
diff -up xmonad-contrib-0.9.1/XMonad/Prompt/Man.hs~ xmonad-contrib-0.9.1/XMonad/Prompt/Man.hs
|
||
|
--- xmonad-contrib-0.9.1/XMonad/Prompt/Man.hs~ 2009-12-17 09:32:25.000000000 +1000
|
||
|
+++ xmonad-contrib-0.9.1/XMonad/Prompt/Man.hs 2010-11-27 00:08:50.000000000 +1000
|
||
|
@@ -31,7 +31,7 @@ import System.Directory
|
||
|
import System.Process
|
||
|
import System.IO
|
||
|
|
||
|
-import qualified Control.Exception as E
|
||
|
+import qualified Control.Exception.Extensible as E
|
||
|
import Control.Monad
|
||
|
import Data.List
|
||
|
import Data.Maybe
|
||
|
@@ -62,7 +62,8 @@ manPrompt c = do
|
||
|
|
||
|
getMans :: IO [String]
|
||
|
getMans = do
|
||
|
- paths <- getCommandOutput "manpath -g 2>/dev/null" `E.catch` \_ -> return []
|
||
|
+ paths <- getCommandOutput "manpath -g 2>/dev/null" `E.catch`
|
||
|
+ \(E.SomeException _) -> return []
|
||
|
let sects = ["man" ++ show n | n <- [1..9 :: Int]]
|
||
|
dirs = [d ++ "/" ++ s | d <- split ':' paths, s <- sects]
|
||
|
mans <- forM dirs $ \d -> do
|
||
|
diff -up xmonad-contrib-0.9.1/XMonad/Util/CustomKeys.hs~ xmonad-contrib-0.9.1/XMonad/Util/CustomKeys.hs
|
||
|
--- xmonad-contrib-0.9.1/XMonad/Util/CustomKeys.hs~ 2009-12-17 09:32:25.000000000 +1000
|
||
|
+++ xmonad-contrib-0.9.1/XMonad/Util/CustomKeys.hs 2010-11-26 23:55:26.000000000 +1000
|
||
|
@@ -77,7 +77,7 @@ customize :: XConfig l
|
||
|
-> (XConfig Layout -> [(KeyMask, KeySym)])
|
||
|
-> (XConfig Layout -> [((KeyMask, KeySym), X ())])
|
||
|
-> Reader (XConfig Layout) (M.Map (KeyMask, KeySym) (X ()))
|
||
|
-customize conf ds is = Reader (keys conf) >>= delete ds >>= insert is
|
||
|
+customize conf ds is = asks (keys conf) >>= delete ds >>= insert is
|
||
|
|
||
|
delete :: (MonadReader r m, Ord a) => (r -> [a]) -> M.Map a b -> m (M.Map a b)
|
||
|
delete dels kmap = asks dels >>= return . foldr M.delete kmap
|
||
|
diff -up xmonad-contrib-0.9.1/XMonad/Util/NamedWindows.hs~ xmonad-contrib-0.9.1/XMonad/Util/NamedWindows.hs
|
||
|
--- xmonad-contrib-0.9.1/XMonad/Util/NamedWindows.hs~ 2009-12-17 09:32:25.000000000 +1000
|
||
|
+++ xmonad-contrib-0.9.1/XMonad/Util/NamedWindows.hs 2010-11-27 00:05:09.000000000 +1000
|
||
|
@@ -24,7 +24,7 @@ module XMonad.Util.NamedWindows (
|
||
|
|
||
|
import Prelude hiding ( catch )
|
||
|
import Control.Applicative ( (<$>) )
|
||
|
-import Control.Exception ( bracket, catch )
|
||
|
+import Control.Exception.Extensible ( bracket, catch, SomeException(..) )
|
||
|
import Data.Maybe ( fromMaybe, listToMaybe )
|
||
|
|
||
|
import qualified XMonad.StackSet as W ( peek )
|
||
|
@@ -50,11 +50,11 @@ getName w = withDisplay $ \d -> do
|
||
|
let getIt = bracket getProp (xFree . tp_value) (fmap (`NW` w) . copy)
|
||
|
|
||
|
getProp = (internAtom d "_NET_WM_NAME" False >>= getTextProperty d w)
|
||
|
- `catch` \_ -> getTextProperty d w wM_NAME
|
||
|
+ `catch` \(SomeException _) -> getTextProperty d w wM_NAME
|
||
|
|
||
|
copy prop = fromMaybe "" . listToMaybe <$> wcTextPropertyToTextList d prop
|
||
|
|
||
|
- io $ getIt `catch` \_ -> ((`NW` w) . resName) `fmap` getClassHint d w
|
||
|
+ io $ getIt `catch` \(SomeException _) -> ((`NW` w) . resName) `fmap` getClassHint d w
|
||
|
|
||
|
unName :: NamedWindow -> Window
|
||
|
unName (NW _ w) = w
|
||
|
diff -up xmonad-contrib-0.9.1/XMonad/Util/Run.hs~ xmonad-contrib-0.9.1/XMonad/Util/Run.hs
|
||
|
--- xmonad-contrib-0.9.1/XMonad/Util/Run.hs~ 2009-12-17 09:32:25.000000000 +1000
|
||
|
+++ xmonad-contrib-0.9.1/XMonad/Util/Run.hs 2010-11-27 00:02:32.000000000 +1000
|
||
|
@@ -33,8 +33,9 @@ module XMonad.Util.Run (
|
||
|
|
||
|
import System.Posix.IO
|
||
|
import System.Posix.Process (executeFile, forkProcess, createSession)
|
||
|
+import System.Posix.Types (ProcessID)
|
||
|
import Control.Concurrent (threadDelay)
|
||
|
-import Control.Exception (try) -- use OldException with base 4
|
||
|
+import Control.Exception.Extensible (try,SomeException)
|
||
|
import System.IO
|
||
|
import System.Process (runInteractiveProcess)
|
||
|
import XMonad
|
||
|
@@ -107,7 +108,9 @@ it makes use of shell interpretation by
|
||
|
interpolation, whereas the safeSpawn example can be safe because
|
||
|
Firefox doesn't need any arguments if it is just being started. -}
|
||
|
safeSpawn :: MonadIO m => FilePath -> [String] -> m ()
|
||
|
-safeSpawn prog args = liftIO (try (forkProcess $ executeFile prog True args Nothing) >> return ())
|
||
|
+safeSpawn prog args = liftIO $ do
|
||
|
+ try $ forkProcess $ executeFile prog True args Nothing :: IO (Either SomeException ProcessID)
|
||
|
+ return ()
|
||
|
|
||
|
-- | Like 'safeSpawn', but only takes a program (and no arguments for it). eg.
|
||
|
--
|
||
|
diff -up xmonad-contrib-0.9.1/XMonad/Util/XSelection.hs~ xmonad-contrib-0.9.1/XMonad/Util/XSelection.hs
|
||
|
--- xmonad-contrib-0.9.1/XMonad/Util/XSelection.hs~ 2009-12-17 09:32:25.000000000 +1000
|
||
|
+++ xmonad-contrib-0.9.1/XMonad/Util/XSelection.hs 2010-11-27 00:04:16.000000000 +1000
|
||
|
@@ -24,7 +24,7 @@ module XMonad.Util.XSelection ( -- * Us
|
||
|
putSelection) where
|
||
|
|
||
|
import Control.Concurrent (forkIO)
|
||
|
-import Control.Exception as E (catch)
|
||
|
+import Control.Exception.Extensible as E (catch,SomeException(..))
|
||
|
import Control.Monad(Monad (return, (>>)), Functor(..), liftM, join)
|
||
|
import Data.Char (ord)
|
||
|
import Data.Maybe (fromMaybe)
|
||
|
@@ -69,8 +69,8 @@ getSelection = io $ do
|
||
|
ty <- E.catch
|
||
|
(E.catch
|
||
|
(internAtom dpy "UTF8_STRING" False)
|
||
|
- (\_ -> internAtom dpy "COMPOUND_TEXT" False))
|
||
|
- (\_ -> internAtom dpy "sTring" False)
|
||
|
+ (\(E.SomeException _) -> internAtom dpy "COMPOUND_TEXT" False))
|
||
|
+ (\(E.SomeException _) -> internAtom dpy "sTring" False)
|
||
|
clp <- internAtom dpy "BLITZ_SEL_STRING" False
|
||
|
xConvertSelection dpy p ty clp win currentTime
|
||
|
allocaXEvent $ \e -> do
|
||
|
diff -up xmonad-contrib-0.9.1/xmonad-contrib.cabal~ xmonad-contrib-0.9.1/xmonad-contrib.cabal
|
||
|
--- xmonad-contrib-0.9.1/xmonad-contrib.cabal~ 2009-12-17 09:32:25.000000000 +1000
|
||
|
+++ xmonad-contrib-0.9.1/xmonad-contrib.cabal 2010-11-27 00:01:18.000000000 +1000
|
||
|
@@ -40,7 +40,14 @@ flag testing
|
||
|
|
||
|
library
|
||
|
if flag(small_base)
|
||
|
- build-depends: base >= 3 && < 4, containers, directory, process, random, old-time, old-locale
|
||
|
+ build-depends: base >= 3 && < 5,
|
||
|
+ containers,
|
||
|
+ directory,
|
||
|
+ extensible-exceptions,
|
||
|
+ old-locale,
|
||
|
+ old-time,
|
||
|
+ process,
|
||
|
+ random
|
||
|
else
|
||
|
build-depends: base < 3
|
||
|
|
||
|
@@ -56,6 +63,9 @@ library
|
||
|
if flag(testing)
|
||
|
ghc-options: -fwarn-tabs -Werror
|
||
|
|
||
|
+ if impl(ghc >= 6.12.1)
|
||
|
+ ghc-options: -fno-warn-unused-do-bind
|
||
|
+
|
||
|
if impl (ghc == 6.10.1) && arch (x86_64)
|
||
|
ghc-options: -O0
|
||
|
|