[commit: ghc] master: Remove now redundant CPP (cf6b4d1)
git at git.haskell.org
git at git.haskell.org
Sat Sep 9 08:54:59 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/cf6b4d1c603c0e81eeae8d4e4d8025e84ca5d63b/ghc
>---------------------------------------------------------------
commit cf6b4d1c603c0e81eeae8d4e4d8025e84ca5d63b
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Sat Sep 9 10:53:56 2017 +0200
Remove now redundant CPP
Resulting from requiring to boot with GHC 8.0 or later
>---------------------------------------------------------------
cf6b4d1c603c0e81eeae8d4e4d8025e84ca5d63b
compiler/prelude/PrelRules.hs | 4 ----
compiler/prelude/PrimOp.hs | 2 --
compiler/utils/UniqMap.hs | 5 -----
3 files changed, 11 deletions(-)
diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs
index 8ee0f82..13f4f12 100644
--- a/compiler/prelude/PrelRules.hs
+++ b/compiler/prelude/PrelRules.hs
@@ -56,9 +56,7 @@ import Coercion (mkUnbranchedAxInstCo,mkSymCo,Role(..))
import Control.Applicative ( Alternative(..) )
import Control.Monad
-#if __GLASGOW_HASKELL__ > 710
import qualified Control.Monad.Fail as MonadFail
-#endif
import Data.Bits as Bits
import qualified Data.ByteString as BS
import Data.Int
@@ -651,10 +649,8 @@ instance Monad RuleM where
Just r -> runRuleM (g r) dflags iu e
fail _ = mzero
-#if __GLASGOW_HASKELL__ > 710
instance MonadFail.MonadFail RuleM where
fail _ = mzero
-#endif
instance Alternative RuleM where
empty = RuleM $ \_ _ _ -> Nothing
diff --git a/compiler/prelude/PrimOp.hs b/compiler/prelude/PrimOp.hs
index 3a84906..79bec86 100644
--- a/compiler/prelude/PrimOp.hs
+++ b/compiler/prelude/PrimOp.hs
@@ -7,9 +7,7 @@
{-# LANGUAGE CPP #-}
-- The default is a bit too low for the quite large primOpInfo definition
-#if __GLASGOW_HASKELL__ >= 801
{-# OPTIONS_GHC -fmax-pmcheck-iterations=10000000 #-}
-#endif
module PrimOp (
PrimOp(..), PrimOpVecCat(..), allThePrimOps,
diff --git a/compiler/utils/UniqMap.hs b/compiler/utils/UniqMap.hs
index 012409b..5bd609e 100644
--- a/compiler/utils/UniqMap.hs
+++ b/compiler/utils/UniqMap.hs
@@ -1,6 +1,5 @@
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE TupleSections #-}
-{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# OPTIONS_GHC -Wall #-}
@@ -50,9 +49,7 @@ import UniqFM
import Unique
import Outputable
-#if __GLASGOW_HASKELL__ > 710
import Data.Semigroup ( Semigroup(..) )
-#endif
import Data.Coerce
import Data.Maybe
import Data.Typeable
@@ -63,10 +60,8 @@ newtype UniqMap k a = UniqMap (UniqFM (k, a))
deriving (Data, Eq, Functor, Typeable)
type role UniqMap nominal representational
-#if __GLASGOW_HASKELL__ > 710
instance Semigroup (UniqMap k a) where
(<>) = plusUniqMap
-#endif
instance Monoid (UniqMap k a) where
mempty = emptyUniqMap
More information about the ghc-commits
mailing list