[commit: haddock] wip/api-ann-hstylit-5: Remove Traversable instance for GenLocated SrcSpan (5ccca44)

git at git.haskell.org git at git.haskell.org
Wed Jul 8 08:35:10 UTC 2015


Repository : ssh://git@git.haskell.org/haddock

On branch  : wip/api-ann-hstylit-5
Link       : http://git.haskell.org/haddock.git/commitdiff/5ccca44efa0833227622973276c4f63566fc27ab

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

commit 5ccca44efa0833227622973276c4f63566fc27ab
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date:   Tue Dec 16 16:06:21 2014 +0200

    Remove Traversable instance for GenLocated SrcSpan


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

5ccca44efa0833227622973276c4f63566fc27ab
 src/Haddock/GhcUtils.hs | 7 -------
 1 file changed, 7 deletions(-)

diff --git a/src/Haddock/GhcUtils.hs b/src/Haddock/GhcUtils.hs
index c33c27b..918edab 100644
--- a/src/Haddock/GhcUtils.hs
+++ b/src/Haddock/GhcUtils.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE CPP #-}
 {-# LANGUAGE FlexibleInstances, ViewPatterns #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 {-# OPTIONS_HADDOCK hide #-}
@@ -186,12 +185,6 @@ before = (<) `on` getLoc
 instance Foldable (GenLocated l) where
   foldMap f (L _ x) = f x
 
-#if __GLASGOW_HASKELL__ < 709
-instance Traversable (GenLocated l) where
-  mapM f (L l x) = (return . L l) =<< f x
-  traverse f (L l x) = L l <$> f x
-#endif
-
 -------------------------------------------------------------------------------
 -- * NamedThing instances
 -------------------------------------------------------------------------------



More information about the ghc-commits mailing list