diff options
author | Ryan Scott <ryan.gl.scott@gmail.com> | 2017-08-01 09:48:52 -0400 |
---|---|---|
committer | Ben Gamari <ben@smart-cactus.org> | 2017-08-01 10:37:34 -0400 |
commit | c13720c8c6047844f659ad4ce684946b80c99bee (patch) | |
tree | 9c6462bf94d69daa318e5a4a9e2d84981743e1ec /compiler/utils | |
parent | b311096c5cf4b669dcfceb99561ac6e1c4cca0cd (diff) | |
download | haskell-c13720c8c6047844f659ad4ce684946b80c99bee.tar.gz |
Drop GHC 7.10 compatibility
GHC 8.2.1 is out, so now GHC's support window only extends back to GHC
8.0. This means we can delete gobs of code that was only used for GHC
7.10 support. Hooray!
Test Plan: ./validate
Reviewers: hvr, bgamari, austin, goldfire, simonmar
Reviewed By: bgamari
Subscribers: Phyx, rwbarton, thomie
Differential Revision: https://phabricator.haskell.org/D3781
Diffstat (limited to 'compiler/utils')
-rw-r--r-- | compiler/utils/IOEnv.hs | 7 | ||||
-rw-r--r-- | compiler/utils/MonadUtils.hs | 5 | ||||
-rw-r--r-- | compiler/utils/OrdList.hs | 5 | ||||
-rw-r--r-- | compiler/utils/Outputable.hs | 4 | ||||
-rw-r--r-- | compiler/utils/UniqFM.hs | 4 | ||||
-rw-r--r-- | compiler/utils/UniqSet.hs | 5 | ||||
-rw-r--r-- | compiler/utils/Util.hs | 33 |
7 files changed, 4 insertions, 59 deletions
diff --git a/compiler/utils/IOEnv.hs b/compiler/utils/IOEnv.hs index 29854c51fe..5a7ccd9972 100644 --- a/compiler/utils/IOEnv.hs +++ b/compiler/utils/IOEnv.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP #-} - -- -- (c) The University of Glasgow 2002-2006 -- @@ -41,9 +39,7 @@ import Data.IORef ( IORef, newIORef, readIORef, writeIORef, modifyIORef, import System.IO.Unsafe ( unsafeInterleaveIO ) import System.IO ( fixIO ) import Control.Monad -#if __GLASGOW_HASKELL__ > 710 import qualified Control.Monad.Fail as MonadFail -#endif import MonadUtils import Control.Applicative (Alternative(..)) @@ -62,11 +58,8 @@ instance Monad (IOEnv m) where (>>) = (*>) fail _ = failM -- Ignore the string -#if __GLASGOW_HASKELL__ > 710 instance MonadFail.MonadFail (IOEnv m) where fail _ = failM -- Ignore the string -#endif - instance Applicative (IOEnv m) where pure = returnM diff --git a/compiler/utils/MonadUtils.hs b/compiler/utils/MonadUtils.hs index 93a835e04e..d6fb31731e 100644 --- a/compiler/utils/MonadUtils.hs +++ b/compiler/utils/MonadUtils.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP #-} - -- | Utilities related to Monad and Applicative classes -- Mostly for backwards compatibility. @@ -34,9 +32,6 @@ import Maybes import Control.Monad import Control.Monad.Fix import Control.Monad.IO.Class -#if __GLASGOW_HASKELL__ < 800 -import Control.Monad.Trans.Error () -- for orphan `instance MonadPlus IO` -#endif ------------------------------------------------------------------------------- -- Lift combinators diff --git a/compiler/utils/OrdList.hs b/compiler/utils/OrdList.hs index 3c5b9d7380..1660090ba7 100644 --- a/compiler/utils/OrdList.hs +++ b/compiler/utils/OrdList.hs @@ -9,7 +9,6 @@ Provide trees (of instructions), so that lists of instructions can be appended in linear time. -} -{-# LANGUAGE CPP #-} module OrdList ( OrdList, nilOL, isNilOL, unitOL, appOL, consOL, snocOL, concatOL, lastOL, @@ -18,10 +17,8 @@ module OrdList ( import Outputable -#if __GLASGOW_HASKELL__ > 710 import Data.Semigroup ( Semigroup ) import qualified Data.Semigroup as Semigroup -#endif infixl 5 `appOL` infixl 5 `snocOL` @@ -39,10 +36,8 @@ data OrdList a instance Outputable a => Outputable (OrdList a) where ppr ol = ppr (fromOL ol) -- Convert to list and print that -#if __GLASGOW_HASKELL__ > 710 instance Semigroup (OrdList a) where (<>) = appOL -#endif instance Monoid (OrdList a) where mempty = nilOL diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs index 4107e5beef..de27546ac4 100644 --- a/compiler/utils/Outputable.hs +++ b/compiler/utils/Outputable.hs @@ -122,6 +122,7 @@ import Data.List (intersperse) import GHC.Fingerprint import GHC.Show ( showMultiLineString ) +import GHC.Stack ( callStack, prettyCallStack ) {- ************************************************************************ @@ -1130,7 +1131,8 @@ doOrDoes _ = text "do" callStackDoc :: HasCallStack => SDoc callStackDoc = - hang (text "Call stack:") 4 (vcat $ map text $ lines prettyCurrentCallStack) + hang (text "Call stack:") + 4 (vcat $ map text $ lines (prettyCallStack callStack)) pprPanic :: HasCallStack => String -> SDoc -> a -- ^ Throw an exception saying "bug in GHC" diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs index 71a092b28e..8ea8ba4537 100644 --- a/compiler/utils/UniqFM.hs +++ b/compiler/utils/UniqFM.hs @@ -85,10 +85,8 @@ import qualified Data.Monoid as Mon import qualified Data.IntSet as S import Data.Typeable import Data.Data -#if __GLASGOW_HASKELL__ > 710 import Data.Semigroup ( Semigroup ) import qualified Data.Semigroup as Semigroup -#endif newtype UniqFM ele = UFM (M.IntMap ele) @@ -358,10 +356,8 @@ equalKeysUFM (UFM m1) (UFM m2) = M.keys m1 == M.keys m2 -- Instances -#if __GLASGOW_HASKELL__ > 710 instance Semigroup (UniqFM a) where (<>) = plusUFM -#endif instance Monoid (UniqFM a) where mempty = emptyUFM diff --git a/compiler/utils/UniqSet.hs b/compiler/utils/UniqSet.hs index f29a1e6e1f..fcac865ea8 100644 --- a/compiler/utils/UniqSet.hs +++ b/compiler/utils/UniqSet.hs @@ -9,7 +9,6 @@ Based on @UniqFMs@ (as you would expect). Basically, the things need to be in class @Uniquable@. -} {-# LANGUAGE GeneralizedNewtypeDeriving #-} -{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} module UniqSet ( @@ -53,9 +52,7 @@ import Data.Coerce import Outputable import Data.Foldable (foldl') import Data.Data -#if __GLASGOW_HASKELL__ >= 801 import qualified Data.Semigroup -#endif -- Note [UniqSet invariant] -- ~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -189,10 +186,8 @@ unsafeUFMToUniqSet = UniqSet instance Outputable a => Outputable (UniqSet a) where ppr = pprUniqSet ppr -#if __GLASGOW_HASKELL__ >= 801 instance Data.Semigroup.Semigroup (UniqSet a) where (<>) = mappend -#endif instance Monoid (UniqSet a) where mempty = UniqSet mempty UniqSet s `mappend` UniqSet t = UniqSet (s `mappend` t) diff --git a/compiler/utils/Util.hs b/compiler/utils/Util.hs index 35a6340fd4..6146bf0113 100644 --- a/compiler/utils/Util.hs +++ b/compiler/utils/Util.hs @@ -4,11 +4,6 @@ {-# LANGUAGE KindSignatures #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE BangPatterns #-} -#if __GLASGOW_HASKELL__ < 800 --- For CallStack business -{-# LANGUAGE ImplicitParams #-} -{-# LANGUAGE FlexibleContexts #-} -#endif -- | Highly random utility functions -- @@ -124,12 +119,8 @@ module Util ( hashString, -- * Call stacks -#if MIN_VERSION_GLASGOW_HASKELL(7,10,2,0) - GHC.Stack.CallStack, -#endif HasCallStack, HasDebugCallStack, - prettyCurrentCallStack, -- * Utils for flags OverridingBool(..), @@ -147,7 +138,7 @@ import System.IO.Unsafe ( unsafePerformIO ) import Data.List hiding (group) import GHC.Exts -import qualified GHC.Stack +import GHC.Stack (HasCallStack) import Control.Applicative ( liftA2 ) import Control.Monad ( liftM ) @@ -1368,16 +1359,6 @@ mulHi a b = fromIntegral (r `shiftR` 32) where r :: Int64 r = fromIntegral a * fromIntegral b --- | A compatibility wrapper for the @GHC.Stack.HasCallStack@ constraint. -#if __GLASGOW_HASKELL__ >= 800 -type HasCallStack = GHC.Stack.HasCallStack -#elif MIN_VERSION_GLASGOW_HASKELL(7,10,2,0) -type HasCallStack = (?callStack :: GHC.Stack.CallStack) --- CallStack wasn't present in GHC 7.10.1, disable callstacks in stage 1 -#else -type HasCallStack = (() :: Constraint) -#endif - -- | A call stack constraint, but only when 'isDebugOn'. #if defined(DEBUG) type HasDebugCallStack = HasCallStack @@ -1385,18 +1366,6 @@ type HasDebugCallStack = HasCallStack type HasDebugCallStack = (() :: Constraint) #endif --- | Pretty-print the current callstack -#if __GLASGOW_HASKELL__ >= 800 -prettyCurrentCallStack :: HasCallStack => String -prettyCurrentCallStack = GHC.Stack.prettyCallStack GHC.Stack.callStack -#elif MIN_VERSION_GLASGOW_HASKELL(7,10,2,0) -prettyCurrentCallStack :: (?callStack :: GHC.Stack.CallStack) => String -prettyCurrentCallStack = GHC.Stack.showCallStack ?callStack -#else -prettyCurrentCallStack :: HasCallStack => String -prettyCurrentCallStack = "Call stack unavailable" -#endif - data OverridingBool = Auto | Always |