diff options
author | Herbert Valerio Riedel <hvr@gnu.org> | 2015-12-31 13:47:43 +0100 |
---|---|---|
committer | Herbert Valerio Riedel <hvr@gnu.org> | 2015-12-31 22:35:50 +0100 |
commit | 2f923ce2ab8bad6d01645c735c81bbf1b9ff1e05 (patch) | |
tree | 8a21936336868ae1bdaf5b10eb8a1d58480a4727 /compiler | |
parent | 0d20737860c29169d89c1d5ea728f3848cc28564 (diff) | |
download | haskell-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')
72 files changed, 8 insertions, 285 deletions
diff --git a/compiler/basicTypes/ConLike.hs b/compiler/basicTypes/ConLike.hs index 09ad68b317..c25f8225c7 100644 --- a/compiler/basicTypes/ConLike.hs +++ b/compiler/basicTypes/ConLike.hs @@ -39,9 +39,6 @@ import Type (mkTyConApp) import Data.Function (on) import qualified Data.Data as Data import qualified Data.Typeable -#if __GLASGOW_HASKELL__ <= 708 -import Control.Applicative ((<$>)) -#endif {- ************************************************************************ diff --git a/compiler/basicTypes/FieldLabel.hs b/compiler/basicTypes/FieldLabel.hs index 74ce6039c4..922c3d33e1 100644 --- a/compiler/basicTypes/FieldLabel.hs +++ b/compiler/basicTypes/FieldLabel.hs @@ -56,7 +56,6 @@ Of course, datatypes with no constructors cannot have any fields. -} -{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveFoldable #-} @@ -79,11 +78,6 @@ import Binary import Data.Data -#if __GLASGOW_HASKELL__ < 709 -import Data.Foldable ( Foldable ) -import Data.Traversable ( Traversable ) -#endif - -- | Field labels are just represented as strings; -- they are not necessarily unique (even within a module) type FieldLabelString = FastString diff --git a/compiler/basicTypes/SrcLoc.hs b/compiler/basicTypes/SrcLoc.hs index 524da7805d..04f7ec929e 100644 --- a/compiler/basicTypes/SrcLoc.hs +++ b/compiler/basicTypes/SrcLoc.hs @@ -1,6 +1,5 @@ -- (c) The University of Glasgow, 1992-2006 -{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE DeriveFunctor #-} @@ -85,10 +84,6 @@ import Util import Outputable import FastString -#if __GLASGOW_HASKELL__ < 709 -import Data.Foldable ( Foldable ) -import Data.Traversable ( Traversable ) -#endif import Data.Bits import Data.Data import Data.List diff --git a/compiler/cmm/CmmLayoutStack.hs b/compiler/cmm/CmmLayoutStack.hs index 53cfd11b3c..e87b714d66 100644 --- a/compiler/cmm/CmmLayoutStack.hs +++ b/compiler/cmm/CmmLayoutStack.hs @@ -33,9 +33,7 @@ import Data.Bits import Data.List (nub) import Control.Monad (liftM) -#if __GLASGOW_HASKELL__ >= 709 import Prelude hiding ((<*>)) -#endif #include "HsVersions.h" diff --git a/compiler/cmm/CmmLint.hs b/compiler/cmm/CmmLint.hs index a2ccfbeecf..3f85053514 100644 --- a/compiler/cmm/CmmLint.hs +++ b/compiler/cmm/CmmLint.hs @@ -5,7 +5,7 @@ -- CmmLint: checking the correctness of Cmm statements and expressions -- ----------------------------------------------------------------------------- -{-# LANGUAGE GADTs, CPP #-} +{-# LANGUAGE GADTs #-} module CmmLint ( cmmLint, cmmLintGraph ) where @@ -22,9 +22,6 @@ import Outputable import DynFlags import Control.Monad (liftM, ap) -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..)) -#endif -- Things to check: -- - invariant on CmmBlock in CmmExpr (see comment there) diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs index 719d753a57..af24b17a6f 100644 --- a/compiler/cmm/PprC.hs +++ b/compiler/cmm/PprC.hs @@ -55,10 +55,6 @@ import Data.Word import System.IO import qualified Data.Map as Map import Control.Monad (liftM, ap) -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..)) -#endif - import qualified Data.Array.Unsafe as U ( castSTUArray ) import Data.Array.ST diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index 9cedfcdd62..fde662b317 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -52,9 +52,7 @@ import DynFlags import Control.Monad -#if __GLASGOW_HASKELL__ >= 709 import Prelude hiding ((<*>)) -#endif ------------------------------------------------------------------------ -- Top-level bindings diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index de23443f40..c4ff11a1d0 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -50,9 +50,7 @@ import Outputable import Control.Monad (unless,void) import Control.Arrow (first) -#if __GLASGOW_HASKELL__ >= 709 import Prelude hiding ((<*>)) -#endif ------------------------------------------------------------------------ -- cgExpr: the main function diff --git a/compiler/codeGen/StgCmmExtCode.hs b/compiler/codeGen/StgCmmExtCode.hs index 50015989e0..db03a3883b 100644 --- a/compiler/codeGen/StgCmmExtCode.hs +++ b/compiler/codeGen/StgCmmExtCode.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP #-} - -- | Our extended FCode monad. -- We add a mapping from names to CmmExpr, to support local variable names in @@ -54,9 +52,6 @@ import UniqFM import Unique import Control.Monad (liftM, ap) -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..)) -#endif -- | The environment contains variable definitions or blockids. data Named diff --git a/compiler/codeGen/StgCmmForeign.hs b/compiler/codeGen/StgCmmForeign.hs index 285e92c2ed..1dc430d06c 100644 --- a/compiler/codeGen/StgCmmForeign.hs +++ b/compiler/codeGen/StgCmmForeign.hs @@ -45,11 +45,7 @@ import BasicTypes import Control.Monad -#if __GLASGOW_HASKELL__ >= 709 import Prelude hiding( succ, (<*>) ) -#else -import Prelude hiding( succ ) -#endif ----------------------------------------------------------------------------- -- Code generation for Foreign Calls diff --git a/compiler/codeGen/StgCmmHeap.hs b/compiler/codeGen/StgCmmHeap.hs index bcc5221275..ebff4402d0 100644 --- a/compiler/codeGen/StgCmmHeap.hs +++ b/compiler/codeGen/StgCmmHeap.hs @@ -48,9 +48,7 @@ import DynFlags import FastString( mkFastString, fsLit ) import Panic( sorry ) -#if __GLASGOW_HASKELL__ >= 709 import Prelude hiding ((<*>)) -#endif import Control.Monad (when) import Data.Maybe (isJust) diff --git a/compiler/codeGen/StgCmmLayout.hs b/compiler/codeGen/StgCmmLayout.hs index b46ab5ae14..47ee370212 100644 --- a/compiler/codeGen/StgCmmLayout.hs +++ b/compiler/codeGen/StgCmmLayout.hs @@ -25,9 +25,7 @@ module StgCmmLayout ( #include "HsVersions.h" -#if __GLASGOW_HASKELL__ >= 709 import Prelude hiding ((<*>)) -#endif import StgCmmClosure import StgCmmEnv diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs index 5d3b94f090..84f263cc3c 100644 --- a/compiler/codeGen/StgCmmPrim.hs +++ b/compiler/codeGen/StgCmmPrim.hs @@ -43,9 +43,7 @@ import FastString import Outputable import Util -#if __GLASGOW_HASKELL__ >= 709 import Prelude hiding ((<*>)) -#endif import Data.Bits ((.&.), bit) import Control.Monad (liftM, when) diff --git a/compiler/coreSyn/CorePrep.hs b/compiler/coreSyn/CorePrep.hs index 8b4b13b1ec..adaad613c8 100644 --- a/compiler/coreSyn/CorePrep.hs +++ b/compiler/coreSyn/CorePrep.hs @@ -61,10 +61,6 @@ import MonadUtils ( mapAccumLM ) import Data.List ( mapAccumL ) import Control.Monad -#if __GLASGOW_HASKELL__ < 710 -import Control.Applicative -#endif - {- -- --------------------------------------------------------------------------- -- Overview diff --git a/compiler/coreSyn/MkCore.hs b/compiler/coreSyn/MkCore.hs index 2f1b67fe79..0aac992217 100644 --- a/compiler/coreSyn/MkCore.hs +++ b/compiler/coreSyn/MkCore.hs @@ -80,9 +80,6 @@ import DynFlags import Data.List import Data.Char ( ord ) -#if __GLASGOW_HASKELL__ < 709 -import Data.Word ( Word ) -#endif infixl 4 `mkCoreApp`, `mkCoreApps` diff --git a/compiler/deSugar/MatchLit.hs b/compiler/deSugar/MatchLit.hs index 8fe1b05383..301d3a69e2 100644 --- a/compiler/deSugar/MatchLit.hs +++ b/compiler/deSugar/MatchLit.hs @@ -47,9 +47,6 @@ import qualified GHC.LanguageExtensions as LangExt import Control.Monad import Data.Int -#if __GLASGOW_HASKELL__ < 709 -import Data.Traversable (traverse) -#endif import Data.Word {- diff --git a/compiler/deSugar/PmExpr.hs b/compiler/deSugar/PmExpr.hs index 243665b43e..56e7eb8eb7 100644 --- a/compiler/deSugar/PmExpr.hs +++ b/compiler/deSugar/PmExpr.hs @@ -25,9 +25,6 @@ import SrcLoc import FastString -- sLit import VarSet -#if __GLASGOW_HASKELL__ < 709 -import Data.Functor ((<$>)) -#endif import Data.Maybe (mapMaybe) import Data.List (groupBy, sortBy, nubBy) import Control.Monad.Trans.State.Lazy diff --git a/compiler/ghci/ByteCodeAsm.hs b/compiler/ghci/ByteCodeAsm.hs index ea3066605e..cfb78fbd47 100644 --- a/compiler/ghci/ByteCodeAsm.hs +++ b/compiler/ghci/ByteCodeAsm.hs @@ -36,9 +36,6 @@ import Util -- From iserv import SizedSeq -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..)) -#endif import Control.Monad import Control.Monad.ST ( runST ) import Control.Monad.Trans.Class diff --git a/compiler/ghci/ByteCodeGen.hs b/compiler/ghci/ByteCodeGen.hs index fc72084292..d9a504b649 100644 --- a/compiler/ghci/ByteCodeGen.hs +++ b/compiler/ghci/ByteCodeGen.hs @@ -47,10 +47,6 @@ import OrdList import Data.List import Foreign - -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..)) -#endif import Control.Monad import Data.Char diff --git a/compiler/ghci/RtClosureInspect.hs b/compiler/ghci/RtClosureInspect.hs index f121e929f1..e6d703b743 100644 --- a/compiler/ghci/RtClosureInspect.hs +++ b/compiler/ghci/RtClosureInspect.hs @@ -68,15 +68,8 @@ import Data.Array.Base import Data.Ix import Data.List import qualified Data.Sequence as Seq -#if __GLASGOW_HASKELL__ < 709 -import Data.Monoid (mappend) -#endif import Data.Sequence (viewl, ViewL(..)) -#if __GLASGOW_HASKELL__ >= 709 import Foreign -#else -import Foreign.Safe -#endif import System.IO.Unsafe --------------------------------------------- diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs index 6269a8be30..9b904514a1 100644 --- a/compiler/hsSyn/Convert.hs +++ b/compiler/hsSyn/Convert.hs @@ -6,7 +6,6 @@ This module converts Template Haskell syntax into HsSyn -} -{-# LANGUAGE CPP #-} {-# LANGUAGE ScopedTypeVariables #-} module Convert( convertToHsExpr, convertToPat, convertToHsDecls, @@ -39,9 +38,6 @@ import MonadUtils ( foldrM ) import qualified Data.ByteString as BS import Control.Monad( unless, liftM, ap ) -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..)) -#endif import Data.Char ( chr ) import Data.Word ( Word8 ) diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs index 93dc5a9f10..bc339873fe 100644 --- a/compiler/hsSyn/HsBinds.hs +++ b/compiler/hsSyn/HsBinds.hs @@ -13,7 +13,6 @@ Datatype for: @BindGroup@, @Bind@, @Sig@, @Bind@. {-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types] -- in module PlaceHolder {-# LANGUAGE ConstraintKinds #-} -{-# LANGUAGE CPP #-} {-# LANGUAGE BangPatterns #-} module HsBinds where @@ -44,11 +43,6 @@ import Data.Data hiding ( Fixity ) import Data.List hiding ( foldr ) import Data.Ord import Data.Foldable ( Foldable(..) ) -#if __GLASGOW_HASKELL__ < 709 -import Data.Traversable ( Traversable(..) ) -import Data.Monoid ( mappend ) -import Control.Applicative hiding (empty) -#endif {- ************************************************************************ @@ -1029,8 +1023,6 @@ instance Foldable HsPatSynDetails where foldr1 f (RecordPatSyn args) = Data.List.foldr1 f (map (Data.Foldable.foldr1 f) args) --- TODO: After a few more versions, we should probably use these. -#if __GLASGOW_HASKELL__ >= 709 length (InfixPatSyn _ _) = 2 length (PrefixPatSyn args) = Data.List.length args length (RecordPatSyn args) = Data.List.length args @@ -1042,7 +1034,6 @@ instance Foldable HsPatSynDetails where toList (InfixPatSyn left right) = [left, right] toList (PrefixPatSyn args) = args toList (RecordPatSyn args) = foldMap toList args -#endif instance Traversable HsPatSynDetails where traverse f (InfixPatSyn left right) = InfixPatSyn <$> f left <*> f right diff --git a/compiler/hsSyn/HsDecls.hs b/compiler/hsSyn/HsDecls.hs index 16822981b5..a1f24b457a 100644 --- a/compiler/hsSyn/HsDecls.hs +++ b/compiler/hsSyn/HsDecls.hs @@ -3,7 +3,6 @@ (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 -} -{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable, DeriveFunctor, DeriveFoldable, DeriveTraversable #-} {-# LANGUAGE StandaloneDeriving #-} @@ -110,10 +109,6 @@ import FastString import Bag import Data.Maybe ( fromMaybe ) import Data.Data hiding (TyCon,Fixity) -#if __GLASGOW_HASKELL__ < 709 -import Data.Foldable ( Foldable ) -import Data.Traversable ( Traversable ) -#endif {- ************************************************************************ diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/hsSyn/HsUtils.hs index 9576197b88..f0a657202b 100644 --- a/compiler/hsSyn/HsUtils.hs +++ b/compiler/hsSyn/HsUtils.hs @@ -115,11 +115,6 @@ import Data.Either import Data.Function import Data.List -#if __GLASGOW_HASKELL__ < 709 -import Data.Foldable ( foldMap ) -import Data.Monoid ( mempty, mappend ) -#endif - {- ************************************************************************ * * diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs index 3931b18237..b579b656e6 100644 --- a/compiler/iface/TcIface.hs +++ b/compiler/iface/TcIface.hs @@ -72,9 +72,6 @@ import ListSetOps import Data.List import Control.Monad import qualified Data.Map as Map -#if __GLASGOW_HASKELL__ < 709 -import Data.Traversable ( traverse ) -#endif {- This module takes diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index 82c1eeaaf0..ac352ff9a4 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -57,9 +57,6 @@ import ErrUtils import qualified Stream import Control.Monad (ap) -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..)) -#endif -- ---------------------------------------------------------------------------- -- * Some Data Types diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 0aec7ad2a3..a4aa62a89f 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -34,10 +34,6 @@ import Util import Control.Monad.Trans.Class import Control.Monad.Trans.Writer -#if MIN_VERSION_base(4,8,0) -#else -import Data.Monoid ( Monoid, mappend, mempty ) -#endif #if __GLASGOW_HASKELL__ > 710 import Data.Semigroup ( Semigroup ) import qualified Data.Semigroup as Semigroup diff --git a/compiler/main/CmdLineParser.hs b/compiler/main/CmdLineParser.hs index 823f25ea71..83ac593935 100644 --- a/compiler/main/CmdLineParser.hs +++ b/compiler/main/CmdLineParser.hs @@ -33,9 +33,6 @@ import Data.Function import Data.List import Control.Monad (liftM, ap) -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..)) -#endif -------------------------------------------------------- -- The Flag and OptKind types diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 1da9957599..fcb954e275 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -182,9 +182,7 @@ import Control.Monad import Control.Monad.Trans.Class import Control.Monad.Trans.Writer import Control.Monad.Trans.Reader -#if MIN_VERSION_transformers(0,4,0) import Control.Monad.Trans.Except -#endif import Control.Exception (throwIO) import Data.Bits @@ -195,7 +193,6 @@ import Data.Map (Map) import qualified Data.Map as Map import Data.Set (Set) import qualified Data.Set as Set -import Data.Monoid (Monoid) import Data.Word import System.FilePath import System.Directory @@ -850,10 +847,8 @@ instance (Monad m, HasDynFlags m) => HasDynFlags (ReaderT a m) where instance (Monad m, HasDynFlags m) => HasDynFlags (MaybeT m) where getDynFlags = lift getDynFlags -#if MIN_VERSION_transformers(0,4,0) instance (Monad m, HasDynFlags m) => HasDynFlags (ExceptT e m) where getDynFlags = lift getDynFlags -#endif class ContainsDynFlags t where extractDynFlags :: t -> DynFlags diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index 666ff49c3b..957f48c6e1 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -450,12 +450,7 @@ runGhc mb_top_dir ghc = do -- to this function will create a new session which should not be shared among -- several threads. -#if __GLASGOW_HASKELL__ < 710 --- Pre-AMP change -runGhcT :: (ExceptionMonad m, Functor m) => -#else -runGhcT :: (ExceptionMonad m) => -#endif +runGhcT :: ExceptionMonad m => Maybe FilePath -- ^ See argument to 'initGhcMonad'. -> GhcT m a -- ^ The action to perform. -> m a diff --git a/compiler/main/GhcMonad.hs b/compiler/main/GhcMonad.hs index 02e07c25be..c28e87753d 100644 --- a/compiler/main/GhcMonad.hs +++ b/compiler/main/GhcMonad.hs @@ -188,12 +188,7 @@ instance ExceptionMonad m => ExceptionMonad (GhcT m) where instance MonadIO m => HasDynFlags (GhcT m) where getDynFlags = GhcT $ \(Session r) -> liftM hsc_dflags (liftIO $ readIORef r) -#if __GLASGOW_HASKELL__ < 710 --- Pre-AMP change -instance (ExceptionMonad m, Functor m) => GhcMonad (GhcT m) where -#else -instance (ExceptionMonad m) => GhcMonad (GhcT m) where -#endif +instance ExceptionMonad m => GhcMonad (GhcT m) where getSession = GhcT $ \(Session r) -> liftIO $ readIORef r setSession s' = GhcT $ \(Session r) -> liftIO $ writeIORef r s' diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index f7bff71f1f..e22bf93656 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -77,9 +77,6 @@ import Data.Char ( toUpper ) import Data.List as List import Data.Map (Map) import Data.Set (Set) -#if __GLASGOW_HASKELL__ < 709 -import Data.Monoid hiding ((<>)) -#endif #if __GLASGOW_HASKELL__ > 710 import Data.Semigroup ( Semigroup ) import qualified Data.Semigroup as Semigroup diff --git a/compiler/nativeGen/AsmCodeGen.hs b/compiler/nativeGen/AsmCodeGen.hs index b6272b83de..7d3f98be85 100644 --- a/compiler/nativeGen/AsmCodeGen.hs +++ b/compiler/nativeGen/AsmCodeGen.hs @@ -84,9 +84,6 @@ import Data.List import Data.Maybe import Data.Ord ( comparing ) import Control.Exception -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..)) -#endif import Control.Monad import System.IO diff --git a/compiler/nativeGen/NCGMonad.hs b/compiler/nativeGen/NCGMonad.hs index 35a00270a3..1dde1bc0f7 100644 --- a/compiler/nativeGen/NCGMonad.hs +++ b/compiler/nativeGen/NCGMonad.hs @@ -52,9 +52,6 @@ import DynFlags import Module import Control.Monad ( liftM, ap ) -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative ( Applicative(..) ) -#endif import Compiler.Hoopl ( LabelMap, Label ) diff --git a/compiler/nativeGen/RegAlloc/Linear/State.hs b/compiler/nativeGen/RegAlloc/Linear/State.hs index 9602d251c6..e407a80fe1 100644 --- a/compiler/nativeGen/RegAlloc/Linear/State.hs +++ b/compiler/nativeGen/RegAlloc/Linear/State.hs @@ -1,5 +1,4 @@ {-# LANGUAGE UnboxedTuples #-} -{-# LANGUAGE CPP #-} -- | State monad for the linear register allocator. @@ -44,9 +43,6 @@ import Unique import UniqSupply import Control.Monad (liftM, ap) -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..)) -#endif -- | The register allocator monad type. newtype RegM freeRegs a diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index 1bbbfbf20f..26809db5ad 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -74,9 +74,6 @@ module Lexer ( ) where -- base -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative -#endif import Control.Monad #if __GLASGOW_HASKELL__ > 710 import Control.Monad.Fail diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index 0f380862a4..c8fd1ae37d 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -95,11 +95,7 @@ import Data.List import qualified GHC.LanguageExtensions as LangExt import MonadUtils -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative ((<$>)) -#endif import Control.Monad - import Text.ParserCombinators.ReadP as ReadP import Data.Char diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs index 3e9d7ae35a..49cfa982fb 100644 --- a/compiler/prelude/PrelRules.hs +++ b/compiler/prelude/PrelRules.hs @@ -47,11 +47,7 @@ import Platform import Util import Coercion (mkUnbranchedAxInstCo,mkSymCo,Role(..)) -#if __GLASGOW_HASKELL__ >= 709 import Control.Applicative ( Alternative(..) ) -#else -import Control.Applicative ( Applicative(..), Alternative(..) ) -#endif import Control.Monad #if __GLASGOW_HASKELL__ > 710 diff --git a/compiler/profiling/SCCfinal.hs b/compiler/profiling/SCCfinal.hs index 26e54705c5..69ebb59c1b 100644 --- a/compiler/profiling/SCCfinal.hs +++ b/compiler/profiling/SCCfinal.hs @@ -37,9 +37,6 @@ import SrcLoc import Util import Control.Monad (liftM, ap) -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..)) -#endif stgMassageForProfiling :: DynFlags diff --git a/compiler/rename/RnBinds.hs b/compiler/rename/RnBinds.hs index 5acf9a3f34..49b4dbabf8 100644 --- a/compiler/rename/RnBinds.hs +++ b/compiler/rename/RnBinds.hs @@ -9,8 +9,6 @@ type-synonym declarations; those cannot be done at this stage because they may be affected by renaming (which isn't fully worked out yet). -} -{-# LANGUAGE CPP #-} - module RnBinds ( -- Renaming top-level bindings rnTopBindsLHS, rnTopBindsRHS, rnValBindsRHS, @@ -53,9 +51,6 @@ import qualified GHC.LanguageExtensions as LangExt import Control.Monad import Data.List ( partition, sort ) -#if __GLASGOW_HASKELL__ < 709 -import Data.Traversable ( traverse ) -#endif {- -- ToDo: Put the annotations into the monad, so that they arrive in the proper diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index b4ab632f04..0dd5d7de6e 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -54,9 +54,6 @@ import Control.Monad import Data.List ( sortBy ) import Maybes( orElse, mapMaybe ) import qualified Data.Set as Set ( difference, fromList, toList, null ) -#if __GLASGOW_HASKELL__ < 709 -import Data.Traversable (traverse) -#endif {- @rnSourceDecl@ `renames' declarations. diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 5a58148170..f60a6cf020 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -58,10 +58,6 @@ import qualified GHC.LanguageExtensions as LangExt import Data.List ( (\\), nubBy, partition ) import Control.Monad ( unless, when ) -#if __GLASGOW_HASKELL__ < 709 -import Data.Monoid ( mappend, mempty, mconcat ) -#endif - #include "HsVersions.h" {- diff --git a/compiler/specialise/Specialise.hs b/compiler/specialise/Specialise.hs index d45b72a718..7a3257e79c 100644 --- a/compiler/specialise/Specialise.hs +++ b/compiler/specialise/Specialise.hs @@ -36,9 +36,6 @@ import Outputable import FastString import State -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..)) -#endif import Control.Monad #if __GLASGOW_HASKELL__ > 710 import qualified Control.Monad.Fail as MonadFail diff --git a/compiler/stgSyn/StgLint.hs b/compiler/stgSyn/StgLint.hs index f95ca60289..e8bfe113b6 100644 --- a/compiler/stgSyn/StgLint.hs +++ b/compiler/stgSyn/StgLint.hs @@ -26,9 +26,6 @@ import Util import SrcLoc import Outputable import FastString -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative ( Applicative(..) ) -#endif import Control.Monad import Data.Function diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index 07a06d73ec..c5eec49140 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -44,11 +44,6 @@ import Control.Monad import Data.Map (Map) import qualified Data.Map as Map -#if __GLASGOW_HASKELL__ < 709 -import Prelude hiding ( and ) -import Data.Foldable ( and ) -#endif - #include "HsVersions.h" {- diff --git a/compiler/typecheck/FunDeps.hs b/compiler/typecheck/FunDeps.hs index 3e9e9fd07f..ab7e102d56 100644 --- a/compiler/typecheck/FunDeps.hs +++ b/compiler/typecheck/FunDeps.hs @@ -39,12 +39,6 @@ import Data.List ( nubBy ) import Data.Maybe import Data.Foldable ( fold ) -#if __GLASGOW_HASKELL__ < 709 -import Prelude hiding ( and ) -import Control.Applicative ( (<$>) ) -import Data.Foldable ( and ) -#endif - {- ************************************************************************ * * diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 4edc31207d..fa2b8c8cb5 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -39,13 +39,7 @@ import Data.List ( zip4, foldl' ) import BasicTypes import FastString -#if __GLASGOW_HASKELL__ < 709 -bimap :: (a -> b) -> (c -> d) -> Either a c -> Either b d -bimap f _ (Left x) = Left (f x) -bimap _ f (Right x) = Right (f x) -#else import Data.Bifunctor ( bimap ) -#endif {- ************************************************************************ diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index d480dee9c3..cebb6737ff 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -52,9 +52,6 @@ import qualified GHC.LanguageExtensions as LangExt import Control.Monad ( when ) import Data.List ( partition, mapAccumL, nub, sortBy ) -#if __GLASGOW_HASKELL__ < 709 -import Data.Monoid ( Monoid, mempty, mappend, mconcat ) -#endif #if __GLASGOW_HASKELL__ > 710 import Data.Semigroup ( Semigroup ) import qualified Data.Semigroup as Semigroup diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs index 184aa16334..cca1684a24 100644 --- a/compiler/typecheck/TcEvidence.hs +++ b/compiler/typecheck/TcEvidence.hs @@ -64,10 +64,6 @@ import FastString import SrcLoc import Data.IORef( IORef ) -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative ( (<*>), (<$>) ) -#endif - {- Note [TcCoercions] ~~~~~~~~~~~~~~~~~~ diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs index 8129981abf..281da4049b 100644 --- a/compiler/typecheck/TcFlatten.hs +++ b/compiler/typecheck/TcFlatten.hs @@ -31,9 +31,6 @@ import Control.Monad import MonadUtils ( zipWithAndUnzipM ) import GHC.Exts ( inline ) -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative ( Applicative(..), (<$>) ) -#endif import Control.Arrow ( first ) {- diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs index ad36167a69..330415522a 100644 --- a/compiler/typecheck/TcGenDeriv.hs +++ b/compiler/typecheck/TcGenDeriv.hs @@ -61,9 +61,6 @@ import VarEnv import State import Util import Var -#if __GLASGOW_HASKELL__ < 709 -import MonadUtils -#endif import Outputable import Lexeme import FastString diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index 210b1798e6..a2bbdf8564 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -58,9 +58,6 @@ import Outputable import Util import qualified GHC.LanguageExtensions as LangExt -#if __GLASGOW_HASKELL__ < 709 -import Data.Traversable ( traverse ) -#endif import Control.Monad import Data.List ( partition ) diff --git a/compiler/typecheck/TcMatches.hs b/compiler/typecheck/TcMatches.hs index f7bb726ae8..3f4b6adb63 100644 --- a/compiler/typecheck/TcMatches.hs +++ b/compiler/typecheck/TcMatches.hs @@ -47,10 +47,6 @@ import MkCore import Control.Monad -#if __GLASGOW_HASKELL__ < 709 -import Data.Traversable ( traverse ) -#endif - #include "HsVersions.h" {- diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 9444ef241a..7661d7f651 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -42,9 +42,6 @@ import MkId import TcTyDecls import ConLike import FieldLabel -#if __GLASGOW_HASKELL__ < 709 -import Data.Monoid( mconcat, mappend, mempty ) -#endif import Bag import Util import Data.Maybe diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index eb51ebca92..6114e13a3b 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -51,10 +51,6 @@ import Control.Monad ( when, unless ) import Data.List ( partition ) import Data.Foldable ( fold ) -#if __GLASGOW_HASKELL__ < 709 -import Data.Traversable ( traverse ) -#endif - {- ********************************************************************************* * * diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 3f13c348c0..482aadcc92 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -68,9 +68,6 @@ import qualified GHC.LanguageExtensions as LangExt import Control.Monad import Data.List -#if __GLASGOW_HASKELL__ < 709 -import Data.Monoid ( mempty ) -#endif {- ************************************************************************ diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index 97865f44a7..8e8f3375f3 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -213,9 +213,6 @@ import qualified GHC.LanguageExtensions as LangExt import Data.IORef import Control.Monad (liftM, ap) -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..), (<$>) ) -#endif import Data.Functor.Identity {- diff --git a/compiler/typecheck/TcTypeNats.hs b/compiler/typecheck/TcTypeNats.hs index bb349879d5..e7fb85fdbe 100644 --- a/compiler/typecheck/TcTypeNats.hs +++ b/compiler/typecheck/TcTypeNats.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE LambdaCase, CPP #-} +{-# LANGUAGE LambdaCase #-} module TcTypeNats ( typeNatTyCons @@ -38,10 +38,6 @@ import FastString ( FastString, fsLit ) import qualified Data.Map as Map import Data.Maybe ( isJust ) -#if __GLASGOW_HASKELL__ < 709 -import Data.Traversable ( traverse ) -#endif - {------------------------------------------------------------------------------- Built-in type constructors for functions on type-level nats -} diff --git a/compiler/types/Coercion.hs b/compiler/types/Coercion.hs index f8647a0319..f8a2533d4e 100644 --- a/compiler/types/Coercion.hs +++ b/compiler/types/Coercion.hs @@ -123,12 +123,6 @@ import TysPrim ( eqPhantPrimTyCon ) import ListSetOps import Maybes -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative hiding ( empty ) -import Prelude hiding ( and ) -import Data.Traversable (traverse, sequenceA) -import Data.Foldable ( and ) -#endif import Control.Monad (foldM) import FastString import Control.Arrow ( first ) diff --git a/compiler/types/InstEnv.hs b/compiler/types/InstEnv.hs index b37566a772..6a241ad4ce 100644 --- a/compiler/types/InstEnv.hs +++ b/compiler/types/InstEnv.hs @@ -46,9 +46,6 @@ import Id import FastString import Data.Data ( Data, Typeable ) import Data.Maybe ( isJust, isNothing ) -#if __GLASGOW_HASKELL__ < 709 -import Data.Monoid -#endif {- ************************************************************************ diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index 42263d8b4c..cd2b5873c6 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -221,12 +221,6 @@ import Data.Maybe ( isJust, mapMaybe ) import Control.Monad ( guard ) import Control.Arrow ( first, second ) -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative ( Applicative, (<*>), (<$>), pure ) -import Data.Monoid ( Monoid(..) ) -import Data.Foldable ( foldMap ) -#endif - -- $type_classification -- #type_classification# -- diff --git a/compiler/types/Unify.hs b/compiler/types/Unify.hs index 37c1dc4679..769f505ee0 100644 --- a/compiler/types/Unify.hs +++ b/compiler/types/Unify.hs @@ -41,9 +41,6 @@ import Control.Monad #if __GLASGOW_HASKELL__ > 710 import qualified Control.Monad.Fail as MonadFail #endif -#if __GLASGOW_HASKELL__ < 709 -import Data.Traversable ( traverse ) -#endif import Control.Applicative hiding ( empty ) import qualified Control.Applicative 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) diff --git a/compiler/vectorise/Vectorise/Exp.hs b/compiler/vectorise/Vectorise/Exp.hs index ffc1b9caf2..fd1db9a7f8 100644 --- a/compiler/vectorise/Vectorise/Exp.hs +++ b/compiler/vectorise/Vectorise/Exp.hs @@ -45,9 +45,6 @@ import FastString import DynFlags import Util import UniqDFM (udfmToUfm) -#if __GLASGOW_HASKELL__ < 709 -import MonadUtils -#endif import Control.Monad import Data.Maybe |