[xmonad] darcs patch: Fix error due to removal of catch in GHC7.6
Michael Sloan
mgsloan at gmail.com
Mon Aug 27 02:11:33 CEST 2012
One thing to 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#comment:6
On Sun, Aug 26, 2012 at 4:51 PM, <mgsloan at gmail.com> wrote:
> 1 patch for repository http://code.haskell.org/xmonad:
>
> Sun Aug 26 16:50:22 PDT 2012 mgsloan at gmail.com
> * Fix error due to removal of catch in GHC7.6
>
>
>
> [Fix error due to removal of catch in GHC7.6
> mgsloan at gmail.com**20120826235022
> Ignore-this: bca3c8bbd1a1f9892b1585361a1324fe
> ] {
> hunk ./XMonad/Core.hs 34
>
> import XMonad.StackSet hiding (modify)
>
> +#if __GLASGOW_HASKELL__ < 706
> import Prelude hiding ( catch )
> hunk ./XMonad/Core.hs 36
> +#else
> +import Prelude
> +#endif
> import Codec.Binary.UTF8.String (encodeString)
> import Control.Exception.Extensible (catch, fromException, try, bracket, throw, finally, SomeException(..))
> import Control.Applicative
> hunk ./XMonad/ManageHook.hs 21
>
> module XMonad.ManageHook where
>
> +#if __GLASGOW_HASKELL__ < 706
> import Prelude hiding (catch)
> hunk ./XMonad/ManageHook.hs 23
> +#else
> +import Prelude
> +#endif
> import XMonad.Core
> import Graphics.X11.Xlib.Extras
> import Graphics.X11.Xlib (Display, Window, internAtom, wM_NAME)
> }
>
>
> _______________________________________________
> xmonad mailing list
> xmonad at haskell.org
> http://www.haskell.org/mailman/listinfo/xmonad
>
More information about the xmonad
mailing list