summaryrefslogtreecommitdiff
path: root/compiler/utils
diff options
context:
space:
mode:
authorHerbert Valerio Riedel <hvr@gnu.org>2015-12-31 13:47:43 +0100
committerHerbert Valerio Riedel <hvr@gnu.org>2015-12-31 22:35:50 +0100
commit2f923ce2ab8bad6d01645c735c81bbf1b9ff1e05 (patch)
tree8a21936336868ae1bdaf5b10eb8a1d58480a4727 /compiler/utils
parent0d20737860c29169d89c1d5ea728f3848cc28564 (diff)
downloadhaskell-2f923ce2ab8bad6d01645c735c81bbf1b9ff1e05.tar.gz
Drop pre-AMP compatibility CPP conditionals
Since GHC 8.1/8.2 only needs to be bootstrap-able by GHC 7.10 and GHC 8.0 (and GHC 8.2), we can now finally drop all that pre-AMP compatibility CPP-mess for good! Reviewers: austin, goldfire, bgamari Subscribers: goldfire, thomie, erikd Differential Revision: https://phabricator.haskell.org/D1724
Diffstat (limited to 'compiler/utils')
-rw-r--r--compiler/utils/BooleanFormula.hs10
-rw-r--r--compiler/utils/FastString.hs4
-rw-r--r--compiler/utils/OrdList.hs3
-rw-r--r--compiler/utils/Pair.hs6
-rw-r--r--compiler/utils/State.hs6
-rw-r--r--compiler/utils/Stream.hs6
-rw-r--r--compiler/utils/StringBuffer.hs4
-rw-r--r--compiler/utils/UniqFM.hs3
-rw-r--r--compiler/utils/Util.hs3
9 files changed, 4 insertions, 41 deletions
diff --git a/compiler/utils/BooleanFormula.hs b/compiler/utils/BooleanFormula.hs
index 382431e549..743b8f11c0 100644
--- a/compiler/utils/BooleanFormula.hs
+++ b/compiler/utils/BooleanFormula.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE CPP #-}
+{-# LANGUAGE DeriveDataTypeable, DeriveFunctor, DeriveFoldable,
+ DeriveTraversable #-}
--------------------------------------------------------------------------------
-- | Boolean formulas without quantifiers and without negation.
@@ -6,9 +7,6 @@
--
-- This module is used to represent minimal complete definitions for classes.
--
-{-# LANGUAGE DeriveDataTypeable, DeriveFunctor, DeriveFoldable,
- DeriveTraversable #-}
-
module BooleanFormula (
BooleanFormula(..), LBooleanFormula,
mkFalse, mkTrue, mkAnd, mkOr, mkVar,
@@ -20,10 +18,6 @@ module BooleanFormula (
import Data.List ( nub, intersperse )
import Data.Data
-#if __GLASGOW_HASKELL__ < 709
-import Data.Foldable ( Foldable )
-import Data.Traversable ( Traversable )
-#endif
import MonadUtils
import Outputable
diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs
index e1ef46abe1..ea95d84763 100644
--- a/compiler/utils/FastString.hs
+++ b/compiler/utils/FastString.hs
@@ -115,11 +115,7 @@ import Data.List ( elemIndex )
import GHC.IO ( IO(..), unsafeDupablePerformIO )
-#if __GLASGOW_HASKELL__ >= 709
import Foreign
-#else
-import Foreign.Safe
-#endif
#if STAGE >= 2
import GHC.Conc.Sync (sharedCAF)
diff --git a/compiler/utils/OrdList.hs b/compiler/utils/OrdList.hs
index f5362bb27f..625886d0a7 100644
--- a/compiler/utils/OrdList.hs
+++ b/compiler/utils/OrdList.hs
@@ -18,9 +18,6 @@ module OrdList (
import Outputable
-#if __GLASGOW_HASKELL__ < 709
-import Data.Monoid ( Monoid(..) )
-#endif
#if __GLASGOW_HASKELL__ > 710
import Data.Semigroup ( Semigroup )
import qualified Data.Semigroup as Semigroup
diff --git a/compiler/utils/Pair.hs b/compiler/utils/Pair.hs
index 8747e619ca..d816ad3f98 100644
--- a/compiler/utils/Pair.hs
+++ b/compiler/utils/Pair.hs
@@ -10,12 +10,6 @@ module Pair ( Pair(..), unPair, toPair, swap, pLiftFst, pLiftSnd ) where
#include "HsVersions.h"
import Outputable
-#if __GLASGOW_HASKELL__ < 709
-import Control.Applicative
-import Data.Foldable
-import Data.Monoid
-import Data.Traversable
-#endif
data Pair a = Pair { pFst :: a, pSnd :: a }
-- Note that Pair is a *unary* type constructor
diff --git a/compiler/utils/State.hs b/compiler/utils/State.hs
index a1903cee76..fb6f2c3554 100644
--- a/compiler/utils/State.hs
+++ b/compiler/utils/State.hs
@@ -1,11 +1,7 @@
-{-# LANGUAGE UnboxedTuples, CPP #-}
+{-# LANGUAGE UnboxedTuples #-}
module State where
-#if __GLASGOW_HASKELL__ < 709
-import Control.Applicative
-#endif
-
newtype State s a = State { runState' :: s -> (# a, s #) }
instance Functor (State s) where
diff --git a/compiler/utils/Stream.hs b/compiler/utils/Stream.hs
index fcef97b654..a347206e61 100644
--- a/compiler/utils/Stream.hs
+++ b/compiler/utils/Stream.hs
@@ -5,17 +5,13 @@
-- Monadic streams
--
-- -----------------------------------------------------------------------------
-{-# LANGUAGE CPP #-}
module Stream (
Stream(..), yield, liftIO,
collect, fromList,
Stream.map, Stream.mapM, Stream.mapAccumL
) where
-import Control.Monad
-#if __GLASGOW_HASKELL__ < 709
-import Control.Applicative
-#endif
+import Control.Monad
-- |
-- @Stream m a b@ is a computation in some Monad @m@ that delivers a sequence
diff --git a/compiler/utils/StringBuffer.hs b/compiler/utils/StringBuffer.hs
index 6b39fc8608..7da9f6c22d 100644
--- a/compiler/utils/StringBuffer.hs
+++ b/compiler/utils/StringBuffer.hs
@@ -58,11 +58,7 @@ import GHC.IO.Encoding.Failure ( CodingFailureMode(IgnoreCodingFailure) )
import GHC.Exts
-#if __GLASGOW_HASKELL__ >= 709
import Foreign
-#else
-import Foreign.Safe
-#endif
-- -----------------------------------------------------------------------------
-- The StringBuffer type
diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs
index fa556fb2b1..1dc6cf5655 100644
--- a/compiler/utils/UniqFM.hs
+++ b/compiler/utils/UniqFM.hs
@@ -81,9 +81,6 @@ import qualified Data.Foldable as Foldable
import qualified Data.Traversable as Traversable
import Data.Typeable
import Data.Data
-#if __GLASGOW_HASKELL__ < 709
-import Data.Monoid
-#endif
#if __GLASGOW_HASKELL__ > 710
import Data.Semigroup ( Semigroup )
import qualified Data.Semigroup as Semigroup
diff --git a/compiler/utils/Util.hs b/compiler/utils/Util.hs
index 75c0c79ea2..c0a335c9b2 100644
--- a/compiler/utils/Util.hs
+++ b/compiler/utils/Util.hs
@@ -117,9 +117,6 @@ import Data.List hiding (group)
import GHC.Exts
-#if __GLASGOW_HASKELL__ < 709
-import Control.Applicative (Applicative)
-#endif
import Control.Applicative ( liftA2 )
import Control.Monad ( liftM )
import GHC.IO.Encoding (mkTextEncoding, textEncodingName)