darcs patch: Fix errors due to removal of catch in GHC7.6

1 patch for repository http://code.haskell.org/XMonadContrib: Sun Aug 26 17:12:14 PDT 2012 mgsloan@gmail.com * Fix errors due to removal of catch in GHC7.6 note is that this won't be necessary (but will generate warnings) once this GHC bug is fixed: http://hackage.haskell.org/trac/ghc/ticket/7167

On Mon, Aug 27, 2012 at 2:13 AM,
1 patch for repository http://code.haskell.org/XMonadContrib:
Sun Aug 26 17:12:14 PDT 2012 mgsloan@gmail.com * Fix errors due to removal of catch in GHC7.6 note is that this won't be necessary (but will generate warnings) once this GHC bug is fixed:
Michael, I'm glad you already fixed this. What about xmonad's dependencies? Did you check and fix them too? It'd be great to have releases of at least the dependencies together with or before the ghc 7.6 release. A 0.10.2 release would be called for to make it compat with 7.6 if you ask me. Would that bethe usual process with ghc compat or does it normally lag behind? I mean, these are janitorial patches and nothing intrusive at all, so should be easy to merge.
http://hackage.haskell.org/trac/ghc/ticket/7167
[Fix errors due to removal of catch in GHC7.6 mgsloan@gmail.com**20120827001214 Ignore-this: 90f65c804c49785ee1e3ca03274b8891 note is that this won't be necessary (but will generate warnings) once this GHC bug is fixed:
http://hackage.haskell.org/trac/ghc/ticket/7167 ] { hunk ./XMonad/Actions/TagWindows.hs 1 +{-# LANGUAGE CPP #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Actions.TagWindows hunk ./XMonad/Actions/TagWindows.hs 30 TagPrompt, ) where
+#if __GLASGOW_HASKELL__ < 706 import Prelude hiding (catch) hunk ./XMonad/Actions/TagWindows.hs 32 +#else +import Prelude +#endif import Data.List (nub,sortBy) import Control.Monad import Control.Exception hunk ./XMonad/Hooks/XPropManage.hs 1 -{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE CPP, ScopedTypeVariables #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Hooks.XPropManage hunk ./XMonad/Hooks/XPropManage.hs 21 xPropManageHook, XPropMatch, pmX, pmP ) where
+#if __GLASGOW_HASKELL__ < 706 import Prelude hiding (catch) hunk ./XMonad/Hooks/XPropManage.hs 23 +#else +import Prelude +#endif import Control.Exception import Data.Char (chr) import Data.Monoid (mconcat, Endo(..)) hunk ./XMonad/Layout/WorkspaceDir.hs 1 -{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances, PatternGuards #-} +{-# LANGUAGE CPP, DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances, PatternGuards #-}
----------------------------------------------------------------------------- -- | hunk ./XMonad/Layout/WorkspaceDir.hs 32 WorkspaceDir, ) where
+#if __GLASGOW_HASKELL__ < 706 import Prelude hiding (catch) hunk ./XMonad/Layout/WorkspaceDir.hs 34 +#else +import Prelude +#endif import System.Directory ( setCurrentDirectory, getCurrentDirectory ) import Control.Monad ( when )
hunk ./XMonad/Prompt.hs 1 -{-# LANGUAGE ExistentialQuantification #-} +{-# LANGUAGE CPP, ExistentialQuantification #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Prompt hunk ./XMonad/Prompt.hs 69 , XPState ) where
+#if __GLASGOW_HASKELL__ < 706 import Prelude hiding (catch) hunk ./XMonad/Prompt.hs 71 +#else +import Prelude +#endif
import XMonad hiding (config, cleanMask) import qualified XMonad as X (numberlockMask) hunk ./XMonad/Prompt/DirExec.hs 1 +{-# LANGUAGE CPP #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Prompt.DirExec hunk ./XMonad/Prompt/DirExec.hs 28 , DirExec ) where
+#if __GLASGOW_HASKELL__ < 706 import Prelude hiding (catch) hunk ./XMonad/Prompt/DirExec.hs 30 +#else +import Prelude +#endif import Control.Exception import System.Directory import Control.Monad hunk ./XMonad/Prompt/RunOrRaise.hs 1 +{-# LANGUAGE CPP #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Prompt.RunOrRaise hunk ./XMonad/Prompt/RunOrRaise.hs 30 import XMonad.Actions.WindowGo (runOrRaise) import XMonad.Util.Run (runProcessWithInput)
+#if __GLASGOW_HASKELL__ < 706 import Prelude hiding (catch) hunk ./XMonad/Prompt/RunOrRaise.hs 32 +#else +import Prelude +#endif import Control.Exception import Control.Monad (liftM, liftM2) import System.Directory (doesDirectoryExist, doesFileExist, executable, getPermissions) hunk ./XMonad/Prompt/Shell.hs 1 +{-# LANGUAGE CPP #-} {- | Module : XMonad.Prompt.Shell Copyright : (C) 2007 Andrea Rossato hunk ./XMonad/Prompt/Shell.hs 33 , split ) where
+#if __GLASGOW_HASKELL__ < 706 +import Prelude hiding (catch) +#else +import Prelude +#endif + import Codec.Binary.UTF8.String (encodeString) import Control.Exception import Control.Monad (forM) hunk ./XMonad/Prompt/Shell.hs 43 import Data.List (isPrefixOf) -import Prelude hiding (catch) import System.Directory (doesDirectoryExist, getDirectoryContents) import System.Environment (getEnv) import System.Posix.Files (getFileStatus, isDirectory) hunk ./XMonad/Prompt/Ssh.hs 1 +{-# LANGUAGE CPP #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Prompt.Ssh hunk ./XMonad/Prompt/Ssh.hs 23 Ssh, ) where
+#if __GLASGOW_HASKELL__ < 706 import Prelude hiding (catch) hunk ./XMonad/Prompt/Ssh.hs 25 +#else +import Prelude +#endif
import XMonad import XMonad.Util.Run hunk ./XMonad/Util/Font.hs 35 , fi ) where
+#if __GLASGOW_HASKELL__ < 706 import Prelude hiding (catch) hunk ./XMonad/Util/Font.hs 37 +#else +import Prelude +#endif import XMonad import Foreign import Control.Applicative hunk ./XMonad/Util/Loggers.hs 1 +{-# LANGUAGE CPP #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Util.Loggers hunk ./XMonad/Util/Loggers.hs 56 import XMonad.Util.Font (Align (..)) import XMonad.Util.NamedWindows (getName)
+#if __GLASGOW_HASKELL__ < 706 import Prelude hiding (catch) hunk ./XMonad/Util/Loggers.hs 58 +#else +import Prelude +#endif import Control.Applicative ((<$>)) import Control.Exception import Data.List (isPrefixOf, isSuffixOf) hunk ./XMonad/Util/NamedWindows.hs 1 +{-# LANGUAGE CPP #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Util.NamedWindows hunk ./XMonad/Util/NamedWindows.hs 26 unName ) where
-import Prelude hiding ( catch ) +#if __GLASGOW_HASKELL__ < 706 +import Prelude hiding (catch) +#else +import Prelude +#endif import Control.Applicative ( (<$>) ) import Control.Exception.Extensible ( bracket, catch, SomeException(..) ) import Data.Maybe ( fromMaybe, listToMaybe ) }
participants (2)
-
Carsten Mattner
-
mgsloan@gmail.com