[commit: haddock] master: Follow changes in base (1f3344d)

Ian Lynagh igloo at earth.li
Sat Feb 16 18:22:48 CET 2013


Repository : ssh://darcs.haskell.org//srv/darcs/haddock

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/1f3344df532e561c51de2f07950834e852043f14

>---------------------------------------------------------------

commit 1f3344df532e561c51de2f07950834e852043f14
Author: Ian Lynagh <ian at well-typed.com>
Date:   Sat Feb 16 17:02:07 2013 +0000

    Follow changes in base

>---------------------------------------------------------------

 src/Haddock/Backends/Xhtml.hs |    3 +++
 1 files changed, 3 insertions(+), 0 deletions(-)

diff --git a/src/Haddock/Backends/Xhtml.hs b/src/Haddock/Backends/Xhtml.hs
index 3251477..fde2da6 100644
--- a/src/Haddock/Backends/Xhtml.hs
+++ b/src/Haddock/Backends/Xhtml.hs
@@ -10,6 +10,7 @@
 -- Stability   :  experimental
 -- Portability :  portable
 -----------------------------------------------------------------------------
+{-# LANGUAGE CPP #-}
 module Haddock.Backends.Xhtml (
   ppHtml, copyHtmlBits,
   ppHtmlIndex, ppHtmlContents,
@@ -33,7 +34,9 @@ import Text.XHtml hiding ( name, title, p, quote )
 import Haddock.GhcUtils
 
 import Control.Monad         ( when, unless )
+#if !MIN_VERSION_base(4,7,0)
 import Control.Monad.Instances ( ) -- for Functor Either a
+#endif
 import Data.Char             ( toUpper )
 import Data.List             ( sortBy, groupBy, intercalate )
 import Data.Maybe





More information about the ghc-commits mailing list