summaryrefslogtreecommitdiff
path: root/compiler
diff options
context:
space:
mode:
Diffstat (limited to 'compiler')
-rw-r--r--compiler/basicTypes/BasicTypes.hs2
-rw-r--r--compiler/basicTypes/Module.hs8
-rw-r--r--compiler/basicTypes/RdrName.hs2
-rw-r--r--compiler/hsSyn/HsExpr.hs2
-rw-r--r--compiler/main/SysTools/BaseDir.hs4
-rw-r--r--compiler/utils/Binary.hs26
-rw-r--r--compiler/utils/UniqFM.hs10
-rw-r--r--compiler/utils/UniqMap.hs3
8 files changed, 7 insertions, 50 deletions
diff --git a/compiler/basicTypes/BasicTypes.hs b/compiler/basicTypes/BasicTypes.hs
index d8c3eb739d..c2f442985c 100644
--- a/compiler/basicTypes/BasicTypes.hs
+++ b/compiler/basicTypes/BasicTypes.hs
@@ -442,7 +442,7 @@ compareFixity (Fixity _ prec1 dir1) (Fixity _ prec2 dir2)
-- |Captures the fixity of declarations as they are parsed. This is not
-- necessarily the same as the fixity declaration, as the normal fixity may be
-- overridden using parens or backticks.
-data LexicalFixity = Prefix | Infix deriving (Typeable,Data,Eq)
+data LexicalFixity = Prefix | Infix deriving (Data,Eq)
instance Outputable LexicalFixity where
ppr Prefix = text "Prefix"
diff --git a/compiler/basicTypes/Module.hs b/compiler/basicTypes/Module.hs
index 7fec612234..5b198b33de 100644
--- a/compiler/basicTypes/Module.hs
+++ b/compiler/basicTypes/Module.hs
@@ -551,7 +551,6 @@ instance Outputable ComponentId where
data UnitId
= IndefiniteUnitId {-# UNPACK #-} !IndefUnitId
| DefiniteUnitId {-# UNPACK #-} !DefUnitId
- deriving (Typeable)
unitIdFS :: UnitId -> FastString
unitIdFS (IndefiniteUnitId x) = indefUnitIdFS x
@@ -589,7 +588,7 @@ data IndefUnitId
-- fully instantiated (free module variables are empty)
-- and whether or not a substitution can have any effect.
indefUnitIdFreeHoles :: UniqDSet ModuleName
- } deriving (Typeable)
+ }
instance Eq IndefUnitId where
u1 == u2 = indefUnitIdKey u1 == indefUnitIdKey u2
@@ -644,7 +643,7 @@ indefUnitIdToUnitId dflags iuid =
data IndefModule = IndefModule {
indefModuleUnitId :: IndefUnitId,
indefModuleName :: ModuleName
- } deriving (Typeable, Eq, Ord)
+ } deriving (Eq, Ord)
instance Outputable IndefModule where
ppr (IndefModule uid m) =
@@ -672,7 +671,6 @@ newtype InstalledUnitId =
-- and the hash.
installedUnitIdFS :: FastString
}
- deriving (Typeable)
instance Binary InstalledUnitId where
put_ bh (InstalledUnitId fs) = put_ bh fs
@@ -763,7 +761,7 @@ installedUnitIdEq iuid uid =
-- it only refers to a definite library; i.e., one we have generated
-- code for.
newtype DefUnitId = DefUnitId { unDefUnitId :: InstalledUnitId }
- deriving (Eq, Ord, Typeable)
+ deriving (Eq, Ord)
instance Outputable DefUnitId where
ppr (DefUnitId uid) = ppr uid
diff --git a/compiler/basicTypes/RdrName.hs b/compiler/basicTypes/RdrName.hs
index 2ff0be30d1..6ff114b343 100644
--- a/compiler/basicTypes/RdrName.hs
+++ b/compiler/basicTypes/RdrName.hs
@@ -473,7 +473,7 @@ data Parent = NoParent
| ParentIs { par_is :: Name }
| FldParent { par_is :: Name, par_lbl :: Maybe FieldLabelString }
-- ^ See Note [Parents for record fields]
- deriving (Eq, Data, Typeable)
+ deriving (Eq, Data)
instance Outputable Parent where
ppr NoParent = empty
diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs
index 925967271f..5e43645854 100644
--- a/compiler/hsSyn/HsExpr.hs
+++ b/compiler/hsSyn/HsExpr.hs
@@ -2132,7 +2132,6 @@ data HsSplice id
-- between the two.
ThModFinalizers -- TH finalizers produced by the splice.
(HsSplicedThing id) -- The result of splicing
- deriving Typeable
deriving instance (DataId id) => Data (HsSplice id)
-- | A splice can appear with various decorations wrapped around it. This data
@@ -2173,7 +2172,6 @@ data HsSplicedThing id
= HsSplicedExpr (HsExpr id) -- ^ Haskell Spliced Expression
| HsSplicedTy (HsType id) -- ^ Haskell Spliced Type
| HsSplicedPat (Pat id) -- ^ Haskell Spliced Pattern
- deriving Typeable
deriving instance (DataId id) => Data (HsSplicedThing id)
diff --git a/compiler/main/SysTools/BaseDir.hs b/compiler/main/SysTools/BaseDir.hs
index 2c264b8a2f..c707dac7e7 100644
--- a/compiler/main/SysTools/BaseDir.hs
+++ b/compiler/main/SysTools/BaseDir.hs
@@ -29,11 +29,7 @@ import System.Environment (getExecutablePath)
-- Windows
#if defined(mingw32_HOST_OS)
-#if MIN_VERSION_Win32(2,5,0)
import qualified System.Win32.Types as Win32
-#else
-import qualified System.Win32.Info as Win32
-#endif
import Exception
import Foreign
import Foreign.C.String
diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs
index c3c8ae3ab7..447317ca47 100644
--- a/compiler/utils/Binary.hs
+++ b/compiler/utils/Binary.hs
@@ -79,14 +79,10 @@ import qualified Data.ByteString.Unsafe as BS
import Data.IORef
import Data.Char ( ord, chr )
import Data.Time
-#if MIN_VERSION_base(4,10,0)
import Type.Reflection
import Type.Reflection.Unsafe
import Data.Kind (Type)
import GHC.Exts (TYPE, RuntimeRep(..), VecCount(..), VecElem(..))
-#else
-import Data.Typeable
-#endif
import Control.Monad ( when )
import System.IO as IO
import System.IO.Unsafe ( unsafeInterleaveIO )
@@ -610,7 +606,6 @@ instance Binary (Bin a) where
-- -----------------------------------------------------------------------------
-- Instances for Data.Typeable stuff
-#if MIN_VERSION_base(4,10,0)
instance Binary TyCon where
put_ bh tc = do
put_ bh (tyConPackage tc)
@@ -620,17 +615,7 @@ instance Binary TyCon where
put_ bh (tyConKindRep tc)
get bh =
mkTyCon <$> get bh <*> get bh <*> get bh <*> get bh <*> get bh
-#else
-instance Binary TyCon where
- put_ bh tc = do
- put_ bh (tyConPackage tc)
- put_ bh (tyConModule tc)
- put_ bh (tyConName tc)
- get bh =
- mkTyCon3 <$> get bh <*> get bh <*> get bh
-#endif
-#if MIN_VERSION_base(4,10,0)
instance Binary VecCount where
put_ bh = putByte bh . fromIntegral . fromEnum
get bh = toEnum . fromIntegral <$> getByte bh
@@ -781,17 +766,6 @@ instance Typeable a => Binary (TypeRep (a :: k)) where
instance Binary SomeTypeRep where
put_ bh (SomeTypeRep rep) = putTypeRep bh rep
get = getSomeTypeRep
-#else
-instance Binary TypeRep where
- put_ bh type_rep = do
- let (ty_con, child_type_reps) = splitTyConApp type_rep
- put_ bh ty_con
- put_ bh child_type_reps
- get bh = do
- ty_con <- get bh
- child_type_reps <- get bh
- return (mkTyConApp ty_con child_type_reps)
-#endif
-- -----------------------------------------------------------------------------
-- Lazy reading/writing
diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs
index f0cc197b71..2a9b806178 100644
--- a/compiler/utils/UniqFM.hs
+++ b/compiler/utils/UniqFM.hs
@@ -20,7 +20,6 @@ and ``addToUFM\_C'' and ``Data.IntMap.insertWith'' differ in the order
of arguments of combining function.
-}
-{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# OPTIONS_GHC -Wall #-}
@@ -79,19 +78,16 @@ import Outputable
import Data.List (foldl')
import qualified Data.IntMap as M
-#if MIN_VERSION_containers(0,5,9)
import qualified Data.IntMap.Merge.Lazy as M
import Control.Applicative (Const (..))
import qualified Data.Monoid as Mon
-#endif
import qualified Data.IntSet as S
-import Data.Typeable
import Data.Data
import qualified Data.Semigroup as Semi
newtype UniqFM ele = UFM (M.IntMap ele)
- deriving (Data, Eq, Functor, Typeable)
+ deriving (Data, Eq, Functor)
-- We used to derive Traversable and Foldable, but they were nondeterministic
-- and not obvious at the call site. You can use explicit nonDetEltsUFM
-- and fold a list if needed.
@@ -346,14 +342,10 @@ ufmToIntMap (UFM m) = m
-- Determines whether two 'UniqFm's contain the same keys.
equalKeysUFM :: UniqFM a -> UniqFM b -> Bool
-#if MIN_VERSION_containers(0,5,9)
equalKeysUFM (UFM m1) (UFM m2) = Mon.getAll $ getConst $
M.mergeA (M.traverseMissing (\_ _ -> Const (Mon.All False)))
(M.traverseMissing (\_ _ -> Const (Mon.All False)))
(M.zipWithAMatched (\_ _ _ -> Const (Mon.All True))) m1 m2
-#else
-equalKeysUFM (UFM m1) (UFM m2) = M.keys m1 == M.keys m2
-#endif
-- Instances
diff --git a/compiler/utils/UniqMap.hs b/compiler/utils/UniqMap.hs
index 2dd3cd57ea..1bd51c2b38 100644
--- a/compiler/utils/UniqMap.hs
+++ b/compiler/utils/UniqMap.hs
@@ -54,12 +54,11 @@ import Outputable
import Data.Semigroup as Semi ( Semigroup(..) )
import Data.Coerce
import Data.Maybe
-import Data.Typeable
import Data.Data
-- | Maps indexed by 'Uniquable' keys
newtype UniqMap k a = UniqMap (UniqFM (k, a))
- deriving (Data, Eq, Functor, Typeable)
+ deriving (Data, Eq, Functor)
type role UniqMap nominal representational
instance Semigroup (UniqMap k a) where