diff --git a/.github/workflows/validate.yml b/.github/workflows/validate.yml
index e70c490ed6a5550a915b5ba68e03ce8120ca473b..daa0811440da98661fdd59fa2817117c019c2f8e 100644
--- a/.github/workflows/validate.yml
+++ b/.github/workflows/validate.yml
@@ -80,8 +80,9 @@ jobs:
         # support, so the PR *must* have a changelog entry.
         ghc:
           [
+            "9.12.1",
             "9.10.1",
-            "9.8.2",
+            "9.8.4",
             "9.6.6",
             "9.4.8",
             "9.2.8",
diff --git a/Cabal-syntax/src/Distribution/Backpack.hs b/Cabal-syntax/src/Distribution/Backpack.hs
index 6c61947c6a388ddec6a939771376c7580b7c51fe..e70b9ffc692b271c935d3b2bc929c410c22a5293 100644
--- a/Cabal-syntax/src/Distribution/Backpack.hs
+++ b/Cabal-syntax/src/Distribution/Backpack.hs
@@ -89,7 +89,7 @@ data OpenUnitId
     -- MUST NOT be for an indefinite component; an 'OpenUnitId'
     -- is guaranteed not to have any holes.
     DefiniteUnitId DefUnitId
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 -- TODO: cache holes?
 
@@ -163,7 +163,7 @@ mkDefUnitId cid insts =
 data OpenModule
   = OpenModule OpenUnitId ModuleName
   | OpenModuleVar ModuleName
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 instance Binary OpenModule
 instance Structured OpenModule
diff --git a/Cabal-syntax/src/Distribution/CabalSpecVersion.hs b/Cabal-syntax/src/Distribution/CabalSpecVersion.hs
index 3d1f9418e4a25a8b74e4b0d981c63af2659b5370..a81e8921a949e1af6226f7d8b1a27033865c6e26 100644
--- a/Cabal-syntax/src/Distribution/CabalSpecVersion.hs
+++ b/Cabal-syntax/src/Distribution/CabalSpecVersion.hs
@@ -35,7 +35,7 @@ data CabalSpecVersion
   | -- 3.10: no changes
     CabalSpecV3_12
   | CabalSpecV3_14
-  deriving (Eq, Ord, Show, Read, Enum, Bounded, Typeable, Data, Generic)
+  deriving (Eq, Ord, Show, Read, Enum, Bounded, Data, Generic)
 
 instance Binary CabalSpecVersion
 instance Structured CabalSpecVersion
diff --git a/Cabal-syntax/src/Distribution/Compat/Graph.hs b/Cabal-syntax/src/Distribution/Compat/Graph.hs
index 1a6de3a571bd6ba429c421d957dcc9217a8fa1e8..792cc47ce5f0cd5fe2a079137b78e04bf6a87a0a 100644
--- a/Cabal-syntax/src/Distribution/Compat/Graph.hs
+++ b/Cabal-syntax/src/Distribution/Compat/Graph.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE CPP #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeFamilies #-}
@@ -122,7 +121,6 @@ data Graph a = Graph
   , graphKeyToVertex :: Key a -> Maybe G.Vertex
   , graphBroken :: [(a, [Key a])]
   }
-  deriving (Typeable)
 
 -- NB: Not a Functor! (or Traversable), because you need
 -- to restrict Key a ~ Key b.  We provide our own mapping
diff --git a/Cabal-syntax/src/Distribution/Compat/NonEmptySet.hs b/Cabal-syntax/src/Distribution/Compat/NonEmptySet.hs
index 9e227459e843137990331eafc2476e5dc251e47f..3ece4251b2938bae7512364debe6c197cf1b87bc 100644
--- a/Cabal-syntax/src/Distribution/Compat/NonEmptySet.hs
+++ b/Cabal-syntax/src/Distribution/Compat/NonEmptySet.hs
@@ -33,7 +33,6 @@ import Control.DeepSeq (NFData (..))
 import Data.Data (Data)
 import Data.List.NonEmpty (NonEmpty (..))
 import Data.Semigroup (Semigroup (..))
-import Data.Typeable (Typeable)
 
 import qualified Data.Foldable as F
 import qualified Data.Set as Set
@@ -49,7 +48,7 @@ import Control.Monad (fail)
 
 -- | @since 3.4.0.0
 newtype NonEmptySet a = NES (Set.Set a)
-  deriving (Eq, Ord, Typeable, Data, Read)
+  deriving (Eq, Ord, Data, Read)
 
 -------------------------------------------------------------------------------
 -- Instances
diff --git a/Cabal-syntax/src/Distribution/Compat/Semigroup.hs b/Cabal-syntax/src/Distribution/Compat/Semigroup.hs
index 9db9f6ebe982def74d711cbb0e05e8ffa7c0a8cb..9ebc7f0f7f48aee07c2b1114f185536821a07fba 100644
--- a/Cabal-syntax/src/Distribution/Compat/Semigroup.hs
+++ b/Cabal-syntax/src/Distribution/Compat/Semigroup.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE CPP #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
@@ -18,7 +17,6 @@ module Distribution.Compat.Semigroup
   , gmempty
   ) where
 
-import Data.Typeable (Typeable)
 import Distribution.Compat.Binary (Binary)
 import Distribution.Utils.Structured (Structured)
 
@@ -39,7 +37,7 @@ instance Semigroup (First' a) where
 
 -- | A copy of 'Data.Semigroup.Last'.
 newtype Last' a = Last' {getLast' :: a}
-  deriving (Eq, Ord, Read, Show, Generic, Binary, Typeable)
+  deriving (Eq, Ord, Read, Show, Generic, Binary)
 
 instance Structured a => Structured (Last' a)
 
@@ -52,7 +50,7 @@ instance Functor Last' where
 -- | A wrapper around 'Maybe', providing the 'Semigroup' and 'Monoid' instances
 -- implemented for 'Maybe' since @base-4.11@.
 newtype Option' a = Option' {getOption' :: Maybe a}
-  deriving (Eq, Ord, Read, Show, Binary, Generic, Functor, Typeable)
+  deriving (Eq, Ord, Read, Show, Binary, Generic, Functor)
 
 instance Structured a => Structured (Option' a)
 
diff --git a/Cabal-syntax/src/Distribution/Compiler.hs b/Cabal-syntax/src/Distribution/Compiler.hs
index da2405dc6bf13c929e19d009d70db8be67d0ce59..f4471d476000a3cc3ba07df23edb0f12c3f1c89c 100644
--- a/Cabal-syntax/src/Distribution/Compiler.hs
+++ b/Cabal-syntax/src/Distribution/Compiler.hs
@@ -76,7 +76,7 @@ data CompilerFlavor
   | MHS -- MicroHS, see https://github.com/augustss/MicroHs
   | HaskellSuite String -- string is the id of the actual compiler
   | OtherCompiler String
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance Binary CompilerFlavor
 instance Structured CompilerFlavor
@@ -141,7 +141,6 @@ data PerCompilerFlavor v = PerCompilerFlavor v v
     , Read
     , Eq
     , Ord
-    , Typeable
     , Data
     , Functor
     , Foldable
@@ -172,7 +171,7 @@ instance (Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a) where
 -- ------------------------------------------------------------
 
 data CompilerId = CompilerId CompilerFlavor Version
-  deriving (Eq, Generic, Ord, Read, Show, Typeable)
+  deriving (Eq, Generic, Ord, Read, Show)
 
 instance Binary CompilerId
 instance Structured CompilerId
@@ -222,7 +221,7 @@ instance Binary CompilerInfo
 data AbiTag
   = NoAbiTag
   | AbiTag String
-  deriving (Eq, Generic, Show, Read, Typeable)
+  deriving (Eq, Generic, Show, Read)
 
 instance Binary AbiTag
 instance Structured AbiTag
diff --git a/Cabal-syntax/src/Distribution/License.hs b/Cabal-syntax/src/Distribution/License.hs
index f79ef6d05496b7685a137d0d83e576b3db5d5901..bcd2b84b63b36b0f29cff409ae347f9e77f4add1 100644
--- a/Cabal-syntax/src/Distribution/License.hs
+++ b/Cabal-syntax/src/Distribution/License.hs
@@ -111,7 +111,7 @@ data License
     OtherLicense
   | -- | Indicates an erroneous license name.
     UnknownLicense String
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 instance Binary License
 instance Structured License
diff --git a/Cabal-syntax/src/Distribution/ModuleName.hs b/Cabal-syntax/src/Distribution/ModuleName.hs
index 90082d29f065d5c56e9a0765fd38fc09bcd49d08..59c318004a9cd5c4d77a4fdcf9d9abf7b79e8664 100644
--- a/Cabal-syntax/src/Distribution/ModuleName.hs
+++ b/Cabal-syntax/src/Distribution/ModuleName.hs
@@ -40,7 +40,7 @@ import qualified Text.PrettyPrint as Disp
 
 -- | A valid Haskell module name.
 newtype ModuleName = ModuleName ShortText
-  deriving (Eq, Generic, Ord, Read, Show, Typeable, Data)
+  deriving (Eq, Generic, Ord, Read, Show, Data)
 
 unModuleName :: ModuleName -> String
 unModuleName (ModuleName s) = fromShortText s
diff --git a/Cabal-syntax/src/Distribution/SPDX/License.hs b/Cabal-syntax/src/Distribution/SPDX/License.hs
index af271e9115ad5675aaa99aa770e945fab5f65bda..2331e66c669f415ce47749bdb15c23591e1b526e 100644
--- a/Cabal-syntax/src/Distribution/SPDX/License.hs
+++ b/Cabal-syntax/src/Distribution/SPDX/License.hs
@@ -41,7 +41,7 @@ data License
     NONE
   | -- | A valid SPDX License Expression as defined in Appendix IV.
     License LicenseExpression
-  deriving (Show, Read, Eq, Ord, Typeable, Data, Generic)
+  deriving (Show, Read, Eq, Ord, Data, Generic)
 
 instance Binary License
 instance Structured License
diff --git a/Cabal-syntax/src/Distribution/SPDX/LicenseExceptionId.hs b/Cabal-syntax/src/Distribution/SPDX/LicenseExceptionId.hs
index 6d0bb37caba00686faace87b34682e70b7815699..19c2507446d603beea4b981cf722664652a6a767 100644
--- a/Cabal-syntax/src/Distribution/SPDX/LicenseExceptionId.hs
+++ b/Cabal-syntax/src/Distribution/SPDX/LicenseExceptionId.hs
@@ -104,7 +104,7 @@ data LicenseExceptionId
     | Vsftpd_openssl_exception -- ^ @vsftpd-openssl-exception@, vsftpd OpenSSL exception, SPDX License List 3.23, SPDX License List 3.25
     | WxWindows_exception_3_1 -- ^ @WxWindows-exception-3.1@, WxWindows Library Exception 3.1
     | X11vnc_openssl_exception -- ^ @x11vnc-openssl-exception@, x11vnc OpenSSL Exception, SPDX License List 3.23, SPDX License List 3.25
-  deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data, Generic)
+  deriving (Eq, Ord, Enum, Bounded, Show, Read, Data, Generic)
 
 instance Binary LicenseExceptionId where
     put = Binary.putWord8 . fromIntegral . fromEnum
diff --git a/Cabal-syntax/src/Distribution/SPDX/LicenseExpression.hs b/Cabal-syntax/src/Distribution/SPDX/LicenseExpression.hs
index c77314746f8f673a9d24e86b9ce84de206cd7240..2fe784b279292ddcbd3a5d39683e31e8854df1b8 100644
--- a/Cabal-syntax/src/Distribution/SPDX/LicenseExpression.hs
+++ b/Cabal-syntax/src/Distribution/SPDX/LicenseExpression.hs
@@ -43,7 +43,7 @@ data LicenseExpression
   = ELicense !SimpleLicenseExpression !(Maybe LicenseExceptionId)
   | EAnd !LicenseExpression !LicenseExpression
   | EOr !LicenseExpression !LicenseExpression
-  deriving (Show, Read, Eq, Ord, Typeable, Data, Generic)
+  deriving (Show, Read, Eq, Ord, Data, Generic)
 
 -- | Simple License Expressions.
 data SimpleLicenseExpression
@@ -53,7 +53,7 @@ data SimpleLicenseExpression
     ELicenseIdPlus LicenseId
   | -- | A SPDX user defined license reference: For example: @LicenseRef-23@, @LicenseRef-MIT-Style-1@, or @DocumentRef-spdx-tool-1.2:LicenseRef-MIT-Style-2@
     ELicenseRef LicenseRef
-  deriving (Show, Read, Eq, Ord, Typeable, Data, Generic)
+  deriving (Show, Read, Eq, Ord, Data, Generic)
 
 simpleLicenseExpression :: LicenseId -> LicenseExpression
 simpleLicenseExpression i = ELicense (ELicenseId i) Nothing
diff --git a/Cabal-syntax/src/Distribution/SPDX/LicenseId.hs b/Cabal-syntax/src/Distribution/SPDX/LicenseId.hs
index 998b17e6c694b2efd4d38b50404557bbaee540b2..3f4d34fe0077ab012e434611064c94416cdd51d1 100644
--- a/Cabal-syntax/src/Distribution/SPDX/LicenseId.hs
+++ b/Cabal-syntax/src/Distribution/SPDX/LicenseId.hs
@@ -674,7 +674,7 @@ data LicenseId
     | ZPL_1_1 -- ^ @ZPL-1.1@, Zope Public License 1.1
     | ZPL_2_0 -- ^ @ZPL-2.0@, Zope Public License 2.0
     | ZPL_2_1 -- ^ @ZPL-2.1@, Zope Public License 2.1
-  deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data)
+  deriving (Eq, Ord, Enum, Bounded, Show, Read, Data)
 
 instance Binary LicenseId where
     -- Word16 is encoded in big endianness
diff --git a/Cabal-syntax/src/Distribution/SPDX/LicenseReference.hs b/Cabal-syntax/src/Distribution/SPDX/LicenseReference.hs
index 949d6c4d15d1c02172112f921a79e34db6c7932e..38f83432692fbf4c4982a40b75836b77f7d12b6f 100644
--- a/Cabal-syntax/src/Distribution/SPDX/LicenseReference.hs
+++ b/Cabal-syntax/src/Distribution/SPDX/LicenseReference.hs
@@ -24,7 +24,7 @@ data LicenseRef = LicenseRef
   { _lrDocument :: !(Maybe String)
   , _lrLicense :: !String
   }
-  deriving (Show, Read, Eq, Ord, Typeable, Data, Generic)
+  deriving (Show, Read, Eq, Ord, Data, Generic)
 
 -- | License reference.
 licenseRef :: LicenseRef -> String
diff --git a/Cabal-syntax/src/Distribution/System.hs b/Cabal-syntax/src/Distribution/System.hs
index 1bf6d598d03f89777b3dcb49097855e943f34aa4..1903ae40fc81ffa67b0072315473cc300153388a 100644
--- a/Cabal-syntax/src/Distribution/System.hs
+++ b/Cabal-syntax/src/Distribution/System.hs
@@ -110,7 +110,7 @@ data OS
   | Wasi
   | Haiku
   | OtherOS String
-  deriving (Eq, Generic, Ord, Show, Read, Typeable, Data)
+  deriving (Eq, Generic, Ord, Show, Read, Data)
 
 instance Binary OS
 instance Structured OS
@@ -213,7 +213,7 @@ data Arch
   | JavaScript
   | Wasm32
   | OtherArch String
-  deriving (Eq, Generic, Ord, Show, Read, Typeable, Data)
+  deriving (Eq, Generic, Ord, Show, Read, Data)
 
 instance Binary Arch
 instance Structured Arch
@@ -284,7 +284,7 @@ buildArch = classifyArch Permissive System.Info.arch
 -- ------------------------------------------------------------
 
 data Platform = Platform Arch OS
-  deriving (Eq, Generic, Ord, Show, Read, Typeable, Data)
+  deriving (Eq, Generic, Ord, Show, Read, Data)
 
 instance Binary Platform
 instance Structured Platform
diff --git a/Cabal-syntax/src/Distribution/Types/AbiDependency.hs b/Cabal-syntax/src/Distribution/Types/AbiDependency.hs
index 2f380d15af211b7237865d401daf84a7fe7f3123..54871978605f18633f7e5ae2e91110b1e577d091 100644
--- a/Cabal-syntax/src/Distribution/Types/AbiDependency.hs
+++ b/Cabal-syntax/src/Distribution/Types/AbiDependency.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 
 module Distribution.Types.AbiDependency where
@@ -27,7 +26,7 @@ data AbiDependency = AbiDependency
   { depUnitId :: Package.UnitId
   , depAbiHash :: Package.AbiHash
   }
-  deriving (Eq, Generic, Read, Show, Typeable)
+  deriving (Eq, Generic, Read, Show)
 
 instance Pretty AbiDependency where
   pretty (AbiDependency uid abi) =
diff --git a/Cabal-syntax/src/Distribution/Types/AbiHash.hs b/Cabal-syntax/src/Distribution/Types/AbiHash.hs
index f4b5d5f85649f85339a49501bfe472edf1d1903a..0fa8f03cfd8df4761d0a2cdc0016bea49a8be323 100644
--- a/Cabal-syntax/src/Distribution/Types/AbiHash.hs
+++ b/Cabal-syntax/src/Distribution/Types/AbiHash.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 
 module Distribution.Types.AbiHash
@@ -26,7 +25,7 @@ import Text.PrettyPrint (text)
 --
 -- @since 2.0.0.2
 newtype AbiHash = AbiHash ShortText
-  deriving (Eq, Show, Read, Generic, Typeable)
+  deriving (Eq, Show, Read, Generic)
 
 -- | Convert 'AbiHash' to 'String'
 --
diff --git a/Cabal-syntax/src/Distribution/Types/Benchmark.hs b/Cabal-syntax/src/Distribution/Types/Benchmark.hs
index 13e5fe104e5317df2e2f351313d855c0f46024c6..6da7ef9dcae258bfc021fd80257f308caf7a44ee 100644
--- a/Cabal-syntax/src/Distribution/Types/Benchmark.hs
+++ b/Cabal-syntax/src/Distribution/Types/Benchmark.hs
@@ -27,7 +27,7 @@ data Benchmark = Benchmark
   , benchmarkInterface :: BenchmarkInterface
   , benchmarkBuildInfo :: BuildInfo
   }
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance Binary Benchmark
 instance Structured Benchmark
diff --git a/Cabal-syntax/src/Distribution/Types/BenchmarkInterface.hs b/Cabal-syntax/src/Distribution/Types/BenchmarkInterface.hs
index 02b208644796db3b5689b67b95ae6f16f4388279..d963404a91e699ec21fb13fb9715a8aa6217460f 100644
--- a/Cabal-syntax/src/Distribution/Types/BenchmarkInterface.hs
+++ b/Cabal-syntax/src/Distribution/Types/BenchmarkInterface.hs
@@ -27,7 +27,7 @@ data BenchmarkInterface
   | -- | A benchmark that does not conform to one of the above
     -- interfaces for the given reason (e.g. unknown benchmark type).
     BenchmarkUnsupported BenchmarkType
-  deriving (Eq, Ord, Generic, Read, Show, Typeable, Data)
+  deriving (Eq, Ord, Generic, Read, Show, Data)
 
 instance Binary BenchmarkInterface
 instance Structured BenchmarkInterface
diff --git a/Cabal-syntax/src/Distribution/Types/BenchmarkType.hs b/Cabal-syntax/src/Distribution/Types/BenchmarkType.hs
index 9dd3fad3ff96625d37a9a2afba4ae296ae47d60a..56fc49e1b630df7618f8127ea386b548c8232838 100644
--- a/Cabal-syntax/src/Distribution/Types/BenchmarkType.hs
+++ b/Cabal-syntax/src/Distribution/Types/BenchmarkType.hs
@@ -22,7 +22,7 @@ data BenchmarkType
     BenchmarkTypeExe Version
   | -- | Some unknown benchmark type e.g. \"type: foo\"
     BenchmarkTypeUnknown String Version
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance Binary BenchmarkType
 instance Structured BenchmarkType
diff --git a/Cabal-syntax/src/Distribution/Types/BuildInfo.hs b/Cabal-syntax/src/Distribution/Types/BuildInfo.hs
index 680b9bf49dbb99486859cb702a2f5f7b0bbe6620..2d7a5edeae11e9ac47980ede1b9a412149d22a33 100644
--- a/Cabal-syntax/src/Distribution/Types/BuildInfo.hs
+++ b/Cabal-syntax/src/Distribution/Types/BuildInfo.hs
@@ -144,7 +144,7 @@ data BuildInfo = BuildInfo
   -- ^ Dependencies specific to a library or executable target
   , mixins :: [Mixin]
   }
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance Binary BuildInfo
 instance Structured BuildInfo
diff --git a/Cabal-syntax/src/Distribution/Types/BuildType.hs b/Cabal-syntax/src/Distribution/Types/BuildType.hs
index b94279eaf2e67fbbe0a8a929361d53a61153e02f..eba66ec5d1deaae152c832a9a52ad876a45dc305 100644
--- a/Cabal-syntax/src/Distribution/Types/BuildType.hs
+++ b/Cabal-syntax/src/Distribution/Types/BuildType.hs
@@ -30,7 +30,7 @@ data BuildType
   | -- | uses user-supplied @Setup.hs@ or @Setup.lhs@ (default)
     Custom
   | Hooks
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance Binary BuildType
 instance Structured BuildType
diff --git a/Cabal-syntax/src/Distribution/Types/ComponentId.hs b/Cabal-syntax/src/Distribution/Types/ComponentId.hs
index ac442941d75d3e7799af044971ac75f3dff89a94..fa770448363703f5e7383b288ad964ec61206bb1 100644
--- a/Cabal-syntax/src/Distribution/Types/ComponentId.hs
+++ b/Cabal-syntax/src/Distribution/Types/ComponentId.hs
@@ -31,7 +31,7 @@ import Text.PrettyPrint (text)
 --
 -- @since 2.0.0.2
 newtype ComponentId = ComponentId ShortText
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 -- | Construct a 'ComponentId' from a 'String'
 --
diff --git a/Cabal-syntax/src/Distribution/Types/ComponentName.hs b/Cabal-syntax/src/Distribution/Types/ComponentName.hs
index 01ed6f7655f3680a9fab6ad16ae697b929d0d22b..b66a5a03867a345f4903cb1262fa509f21e4aae9 100644
--- a/Cabal-syntax/src/Distribution/Types/ComponentName.hs
+++ b/Cabal-syntax/src/Distribution/Types/ComponentName.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE PatternSynonyms #-}
 
@@ -25,14 +24,14 @@ import qualified Text.PrettyPrint as Disp
 data ComponentName
   = CLibName LibraryName
   | CNotLibName NotLibComponentName
-  deriving (Eq, Generic, Ord, Read, Show, Typeable)
+  deriving (Eq, Generic, Ord, Read, Show)
 
 data NotLibComponentName
   = CNLFLibName {toCompName :: UnqualComponentName}
   | CNLExeName {toCompName :: UnqualComponentName}
   | CNLTestName {toCompName :: UnqualComponentName}
   | CNLBenchName {toCompName :: UnqualComponentName}
-  deriving (Eq, Generic, Ord, Read, Show, Typeable)
+  deriving (Eq, Generic, Ord, Read, Show)
 
 pattern CFLibName :: UnqualComponentName -> ComponentName
 pattern CFLibName n = CNotLibName (CNLFLibName n)
diff --git a/Cabal-syntax/src/Distribution/Types/ComponentRequestedSpec.hs b/Cabal-syntax/src/Distribution/Types/ComponentRequestedSpec.hs
index 224b38c839d93da42cdafb73bcb4ae5e636de95f..3adcb7ea1da3df6e81cc180f2e7e085cc606990d 100644
--- a/Cabal-syntax/src/Distribution/Types/ComponentRequestedSpec.hs
+++ b/Cabal-syntax/src/Distribution/Types/ComponentRequestedSpec.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 
 module Distribution.Types.ComponentRequestedSpec
@@ -67,7 +66,7 @@ data ComponentRequestedSpec
       , benchmarksRequested :: Bool
       }
   | OneComponentRequestedSpec ComponentName
-  deriving (Generic, Read, Show, Eq, Typeable)
+  deriving (Generic, Read, Show, Eq)
 
 instance Binary ComponentRequestedSpec
 instance Structured ComponentRequestedSpec
diff --git a/Cabal-syntax/src/Distribution/Types/CondTree.hs b/Cabal-syntax/src/Distribution/Types/CondTree.hs
index 40a591ac8eae8754765c7209db2eaeb684b87e63..c74ffdf639571665f0550d756aa69f76add946e2 100644
--- a/Cabal-syntax/src/Distribution/Types/CondTree.hs
+++ b/Cabal-syntax/src/Distribution/Types/CondTree.hs
@@ -59,7 +59,7 @@ data CondTree v c a = CondNode
   , condTreeConstraints :: c
   , condTreeComponents :: [CondBranch v c a]
   }
-  deriving (Show, Eq, Typeable, Data, Generic, Functor, Foldable, Traversable)
+  deriving (Show, Eq, Data, Generic, Functor, Foldable, Traversable)
 
 instance (Binary v, Binary c, Binary a) => Binary (CondTree v c a)
 instance (Structured v, Structured c, Structured a) => Structured (CondTree v c a)
@@ -80,7 +80,7 @@ data CondBranch v c a = CondBranch
   , condBranchIfTrue :: CondTree v c a
   , condBranchIfFalse :: Maybe (CondTree v c a)
   }
-  deriving (Show, Eq, Typeable, Data, Generic, Functor, Traversable)
+  deriving (Show, Eq, Data, Generic, Functor, Traversable)
 
 -- This instance is written by hand because GHC 8.0.1/8.0.2 infinite
 -- loops when trying to derive it with optimizations.  See
diff --git a/Cabal-syntax/src/Distribution/Types/Condition.hs b/Cabal-syntax/src/Distribution/Types/Condition.hs
index 114c25afa668aef32cea253bd7b3cdd23b47b984..b7bcead95ac2146979c1885c35e98cb8d170138b 100644
--- a/Cabal-syntax/src/Distribution/Types/Condition.hs
+++ b/Cabal-syntax/src/Distribution/Types/Condition.hs
@@ -19,7 +19,7 @@ data Condition c
   | CNot (Condition c)
   | COr (Condition c) (Condition c)
   | CAnd (Condition c) (Condition c)
-  deriving (Show, Eq, Typeable, Data, Generic)
+  deriving (Show, Eq, Data, Generic)
 
 -- | Boolean negation of a 'Condition' value.
 cNot :: Condition a -> Condition a
diff --git a/Cabal-syntax/src/Distribution/Types/ConfVar.hs b/Cabal-syntax/src/Distribution/Types/ConfVar.hs
index 220a6556fbd1e0221725be84ff585e229e979f00..bea2d21db52e7ea9ff08033e2b4fdadbc12fa061 100644
--- a/Cabal-syntax/src/Distribution/Types/ConfVar.hs
+++ b/Cabal-syntax/src/Distribution/Types/ConfVar.hs
@@ -19,7 +19,7 @@ data ConfVar
   | Arch Arch
   | PackageFlag FlagName
   | Impl CompilerFlavor VersionRange
-  deriving (Eq, Show, Typeable, Data, Generic)
+  deriving (Eq, Show, Data, Generic)
 
 instance Binary ConfVar
 instance Structured ConfVar
diff --git a/Cabal-syntax/src/Distribution/Types/Dependency.hs b/Cabal-syntax/src/Distribution/Types/Dependency.hs
index a152c9e3a6881a2e0312463cf4ac6f00985b1e5d..d0d5627002b4a9182da6a148b30bb0df92914151 100644
--- a/Cabal-syntax/src/Distribution/Types/Dependency.hs
+++ b/Cabal-syntax/src/Distribution/Types/Dependency.hs
@@ -41,7 +41,7 @@ data Dependency
       PackageName
       VersionRange
       (NonEmptySet LibraryName)
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 depPkgName :: Dependency -> PackageName
 depPkgName (Dependency pn _ _) = pn
diff --git a/Cabal-syntax/src/Distribution/Types/ExeDependency.hs b/Cabal-syntax/src/Distribution/Types/ExeDependency.hs
index 17a79703fcc9ac94b936d22930365fea0afa602d..849debdbf907917da5521596c6b2ad0005c378c3 100644
--- a/Cabal-syntax/src/Distribution/Types/ExeDependency.hs
+++ b/Cabal-syntax/src/Distribution/Types/ExeDependency.hs
@@ -25,7 +25,7 @@ data ExeDependency
       PackageName
       UnqualComponentName -- name of executable component of package
       VersionRange
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 instance Binary ExeDependency
 instance Structured ExeDependency
diff --git a/Cabal-syntax/src/Distribution/Types/Executable.hs b/Cabal-syntax/src/Distribution/Types/Executable.hs
index a2140e074a744b9cbbbc44189760fc0b195af253..2017a9ba8d2ff705ea8402f6c0183a3728315436 100644
--- a/Cabal-syntax/src/Distribution/Types/Executable.hs
+++ b/Cabal-syntax/src/Distribution/Types/Executable.hs
@@ -26,7 +26,7 @@ data Executable = Executable
   , exeScope :: ExecutableScope
   , buildInfo :: BuildInfo
   }
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance L.HasBuildInfo Executable where
   buildInfo f l = (\x -> l{buildInfo = x}) <$> f (buildInfo l)
diff --git a/Cabal-syntax/src/Distribution/Types/ExecutableScope.hs b/Cabal-syntax/src/Distribution/Types/ExecutableScope.hs
index 1221fae1c1a7b7908600924b41b8d99c4ac43e05..5857fb436c26c559675a1347d2ca7e795275157c 100644
--- a/Cabal-syntax/src/Distribution/Types/ExecutableScope.hs
+++ b/Cabal-syntax/src/Distribution/Types/ExecutableScope.hs
@@ -18,7 +18,7 @@ import qualified Text.PrettyPrint as Disp
 data ExecutableScope
   = ExecutablePublic
   | ExecutablePrivate
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance Pretty ExecutableScope where
   pretty ExecutablePublic = Disp.text "public"
diff --git a/Cabal-syntax/src/Distribution/Types/ExposedModule.hs b/Cabal-syntax/src/Distribution/Types/ExposedModule.hs
index 4afd03a32632bf809542968dd2d26ed40666ccc2..66eede651a4d283407efe745d81f2c2e44580c2b 100644
--- a/Cabal-syntax/src/Distribution/Types/ExposedModule.hs
+++ b/Cabal-syntax/src/Distribution/Types/ExposedModule.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 
 module Distribution.Types.ExposedModule where
@@ -18,7 +17,7 @@ data ExposedModule = ExposedModule
   { exposedName :: ModuleName
   , exposedReexport :: Maybe OpenModule
   }
-  deriving (Eq, Generic, Read, Show, Typeable)
+  deriving (Eq, Generic, Read, Show)
 
 instance Pretty ExposedModule where
   pretty (ExposedModule m reexport) =
diff --git a/Cabal-syntax/src/Distribution/Types/Flag.hs b/Cabal-syntax/src/Distribution/Types/Flag.hs
index eff71748d9f33accda53ddb8c388ca91cf528dbe..9ba76ecd4c4ae1ea534afa3904d4d4a7e896ad93 100644
--- a/Cabal-syntax/src/Distribution/Types/Flag.hs
+++ b/Cabal-syntax/src/Distribution/Types/Flag.hs
@@ -56,7 +56,7 @@ data PackageFlag = MkPackageFlag
   , flagDefault :: Bool
   , flagManual :: Bool
   }
-  deriving (Show, Eq, Typeable, Data, Generic)
+  deriving (Show, Eq, Data, Generic)
 
 instance Binary PackageFlag
 instance Structured PackageFlag
@@ -80,7 +80,7 @@ emptyFlag name =
 --
 -- @since 2.0.0.2
 newtype FlagName = FlagName ShortText
-  deriving (Eq, Generic, Ord, Show, Read, Typeable, Data, NFData)
+  deriving (Eq, Generic, Ord, Show, Read, Data, NFData)
 
 -- | Construct a 'FlagName' from a 'String'
 --
@@ -127,7 +127,7 @@ instance Parsec FlagName where
 --
 -- TODO: Why we record the multiplicity of the flag?
 newtype FlagAssignment = FlagAssignment {getFlagAssignment :: Map.Map FlagName (Int, Bool)}
-  deriving (Binary, Generic, NFData, Typeable)
+  deriving (Binary, Generic, NFData)
 
 instance Structured FlagAssignment
 
diff --git a/Cabal-syntax/src/Distribution/Types/ForeignLib.hs b/Cabal-syntax/src/Distribution/Types/ForeignLib.hs
index 0da75b06cc6a5d09ae955bff5f0be625efda6ca4..c8a1472ca564c9a2a1e2eb2c7cfac272c7f5be40 100644
--- a/Cabal-syntax/src/Distribution/Types/ForeignLib.hs
+++ b/Cabal-syntax/src/Distribution/Types/ForeignLib.hs
@@ -61,9 +61,9 @@ data ForeignLib = ForeignLib
   -- This is a list rather than a maybe field so that we can flatten
   -- the condition trees (for instance, when creating an sdist)
   }
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
-data LibVersionInfo = LibVersionInfo Int Int Int deriving (Data, Eq, Generic, Typeable)
+data LibVersionInfo = LibVersionInfo Int Int Int deriving (Data, Eq, Generic)
 
 instance Ord LibVersionInfo where
   LibVersionInfo c r _ `compare` LibVersionInfo c' r' _ =
diff --git a/Cabal-syntax/src/Distribution/Types/ForeignLibOption.hs b/Cabal-syntax/src/Distribution/Types/ForeignLibOption.hs
index 5ed65410e70c3ec53eea213f198b09f35d119ce9..e56afb7a45b7f73f84ccd62e315859bcfd35722e 100644
--- a/Cabal-syntax/src/Distribution/Types/ForeignLibOption.hs
+++ b/Cabal-syntax/src/Distribution/Types/ForeignLibOption.hs
@@ -22,7 +22,7 @@ data ForeignLibOption
     -- This option is compulsory on Windows and unsupported
     -- on other platforms.
     ForeignLibStandalone
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance Pretty ForeignLibOption where
   pretty ForeignLibStandalone = Disp.text "standalone"
diff --git a/Cabal-syntax/src/Distribution/Types/ForeignLibType.hs b/Cabal-syntax/src/Distribution/Types/ForeignLibType.hs
index 23617b80c48ae031fbb0078a7ca256e2307440b7..6ab73d9e2fb6e1af5df30edf82f6e9b70948cc43 100644
--- a/Cabal-syntax/src/Distribution/Types/ForeignLibType.hs
+++ b/Cabal-syntax/src/Distribution/Types/ForeignLibType.hs
@@ -27,7 +27,7 @@ data ForeignLibType
     ForeignLibNativeStatic
   | -- TODO: Maybe this should record a string?
     ForeignLibTypeUnknown
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance Pretty ForeignLibType where
   pretty ForeignLibNativeShared = Disp.text "native-shared"
diff --git a/Cabal-syntax/src/Distribution/Types/GenericPackageDescription.hs b/Cabal-syntax/src/Distribution/Types/GenericPackageDescription.hs
index 55ec8652304e8c590a46a0ad63f534ede1917324..97f4ed8cccb99ae474d1a2d084bf741941610b3e 100644
--- a/Cabal-syntax/src/Distribution/Types/GenericPackageDescription.hs
+++ b/Cabal-syntax/src/Distribution/Types/GenericPackageDescription.hs
@@ -71,7 +71,7 @@ data GenericPackageDescription = GenericPackageDescription
            )
          ]
   }
-  deriving (Show, Eq, Typeable, Data, Generic)
+  deriving (Show, Eq, Data, Generic)
 
 instance Package GenericPackageDescription where
   packageId = packageId . packageDescription
diff --git a/Cabal-syntax/src/Distribution/Types/IncludeRenaming.hs b/Cabal-syntax/src/Distribution/Types/IncludeRenaming.hs
index c8cb70d91f16d6d7a8e12832007ddddc982df716..411b46d6ce4053435d12752c3dc9fd19ad3d39cf 100644
--- a/Cabal-syntax/src/Distribution/Types/IncludeRenaming.hs
+++ b/Cabal-syntax/src/Distribution/Types/IncludeRenaming.hs
@@ -26,7 +26,7 @@ data IncludeRenaming = IncludeRenaming
   { includeProvidesRn :: ModuleRenaming
   , includeRequiresRn :: ModuleRenaming
   }
-  deriving (Show, Read, Eq, Ord, Typeable, Data, Generic)
+  deriving (Show, Read, Eq, Ord, Data, Generic)
 
 instance Binary IncludeRenaming
 instance Structured IncludeRenaming
diff --git a/Cabal-syntax/src/Distribution/Types/InstalledPackageInfo.hs b/Cabal-syntax/src/Distribution/Types/InstalledPackageInfo.hs
index b3e353876ebe6d20e651fcd3a1ebc6b1c3192654..f57457d2e5b1f5c0ab530bfe3ade0a10ec9639ce 100644
--- a/Cabal-syntax/src/Distribution/Types/InstalledPackageInfo.hs
+++ b/Cabal-syntax/src/Distribution/Types/InstalledPackageInfo.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE TypeFamilies #-}
@@ -95,7 +94,7 @@ data InstalledPackageInfo = InstalledPackageInfo
   , haddockHTMLs :: [FilePath]
   , pkgRoot :: Maybe FilePath
   }
-  deriving (Eq, Generic, Typeable, Read, Show)
+  deriving (Eq, Generic, Read, Show)
 
 instance Binary InstalledPackageInfo
 instance Structured InstalledPackageInfo
diff --git a/Cabal-syntax/src/Distribution/Types/LegacyExeDependency.hs b/Cabal-syntax/src/Distribution/Types/LegacyExeDependency.hs
index 7acf028d0b3c81b323bb8ffc68166272b1861787..f5c08ac2747178eb36edc22db179700953d4da00 100644
--- a/Cabal-syntax/src/Distribution/Types/LegacyExeDependency.hs
+++ b/Cabal-syntax/src/Distribution/Types/LegacyExeDependency.hs
@@ -26,7 +26,7 @@ data LegacyExeDependency
   = LegacyExeDependency
       String
       VersionRange
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 instance Binary LegacyExeDependency
 instance Structured LegacyExeDependency
diff --git a/Cabal-syntax/src/Distribution/Types/Library.hs b/Cabal-syntax/src/Distribution/Types/Library.hs
index 738965ea1670c0cdc7945370646f00c21f38a4dd..fd4b89b6a6a5d4122a3dfc5fa7f8ca9f92a06061 100644
--- a/Cabal-syntax/src/Distribution/Types/Library.hs
+++ b/Cabal-syntax/src/Distribution/Types/Library.hs
@@ -31,7 +31,7 @@ data Library = Library
   -- ^ Whether this multilib can be used as a dependency for other packages.
   , libBuildInfo :: BuildInfo
   }
-  deriving (Generic, Show, Eq, Ord, Read, Typeable, Data)
+  deriving (Generic, Show, Eq, Ord, Read, Data)
 
 instance L.HasBuildInfo Library where
   buildInfo f l = (\x -> l{libBuildInfo = x}) <$> f (libBuildInfo l)
diff --git a/Cabal-syntax/src/Distribution/Types/LibraryName.hs b/Cabal-syntax/src/Distribution/Types/LibraryName.hs
index e31d1e82423c329de24d6d58762c51d5bf288922..6813e8b6c680f1cffa449250feaf6146a32f6bc3 100644
--- a/Cabal-syntax/src/Distribution/Types/LibraryName.hs
+++ b/Cabal-syntax/src/Distribution/Types/LibraryName.hs
@@ -29,7 +29,7 @@ import qualified Text.PrettyPrint as Disp
 data LibraryName
   = LMainLibName
   | LSubLibName UnqualComponentName
-  deriving (Eq, Generic, Ord, Read, Show, Typeable, Data)
+  deriving (Eq, Generic, Ord, Read, Show, Data)
 
 instance Binary LibraryName
 instance Structured LibraryName
diff --git a/Cabal-syntax/src/Distribution/Types/LibraryVisibility.hs b/Cabal-syntax/src/Distribution/Types/LibraryVisibility.hs
index bf113488a5ca40c3a0daf9736f9ba47866a61561..8ebd7d2a19dcc173591143902d6be7b2e81514a3 100644
--- a/Cabal-syntax/src/Distribution/Types/LibraryVisibility.hs
+++ b/Cabal-syntax/src/Distribution/Types/LibraryVisibility.hs
@@ -23,7 +23,7 @@ data LibraryVisibility
     LibraryVisibilityPublic
   | -- | Internal library, default
     LibraryVisibilityPrivate
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance Pretty LibraryVisibility where
   pretty LibraryVisibilityPublic = Disp.text "public"
diff --git a/Cabal-syntax/src/Distribution/Types/Mixin.hs b/Cabal-syntax/src/Distribution/Types/Mixin.hs
index 63fa6e30fd5f043fd8ec86292ea70259171ecb3b..726651d32921c3d70c3b3f20661ffe5f60d64591 100644
--- a/Cabal-syntax/src/Distribution/Types/Mixin.hs
+++ b/Cabal-syntax/src/Distribution/Types/Mixin.hs
@@ -31,7 +31,7 @@ data Mixin = Mixin
   , mixinLibraryName :: LibraryName
   , mixinIncludeRenaming :: IncludeRenaming
   }
-  deriving (Show, Read, Eq, Ord, Typeable, Data, Generic)
+  deriving (Show, Read, Eq, Ord, Data, Generic)
 
 instance Binary Mixin
 instance Structured Mixin
diff --git a/Cabal-syntax/src/Distribution/Types/Module.hs b/Cabal-syntax/src/Distribution/Types/Module.hs
index d58ff1a8ec89143bb3269dc1122e0f6df72bcda5..b04510c803762ac47827856e232540d8165c1366 100644
--- a/Cabal-syntax/src/Distribution/Types/Module.hs
+++ b/Cabal-syntax/src/Distribution/Types/Module.hs
@@ -25,7 +25,7 @@ import qualified Text.PrettyPrint as Disp
 -- the 'InstalledPackageInfo'.
 data Module
   = Module DefUnitId ModuleName
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 instance Binary Module
 instance Structured Module
diff --git a/Cabal-syntax/src/Distribution/Types/ModuleReexport.hs b/Cabal-syntax/src/Distribution/Types/ModuleReexport.hs
index 0dae6002c3c19ac27c0e2f56f43c6dc18d22e821..f7aa1e0a2fe0ce9b3431a8fad57a4b2000e504a3 100644
--- a/Cabal-syntax/src/Distribution/Types/ModuleReexport.hs
+++ b/Cabal-syntax/src/Distribution/Types/ModuleReexport.hs
@@ -24,7 +24,7 @@ data ModuleReexport = ModuleReexport
   , moduleReexportOriginalName :: ModuleName
   , moduleReexportName :: ModuleName
   }
-  deriving (Eq, Ord, Generic, Read, Show, Typeable, Data)
+  deriving (Eq, Ord, Generic, Read, Show, Data)
 
 instance Binary ModuleReexport
 instance Structured ModuleReexport
diff --git a/Cabal-syntax/src/Distribution/Types/ModuleRenaming.hs b/Cabal-syntax/src/Distribution/Types/ModuleRenaming.hs
index 022a321a05567983879cae41e98eb78df60d5eba..d0317205f6a11434d7e044a47fb2f3fbe4082af3 100644
--- a/Cabal-syntax/src/Distribution/Types/ModuleRenaming.hs
+++ b/Cabal-syntax/src/Distribution/Types/ModuleRenaming.hs
@@ -40,7 +40,7 @@ data ModuleRenaming
   | -- | Hiding renaming, e.g., @hiding (A, B)@, bringing all
     -- exported modules into scope except the hidden ones.
     HidingRenaming [ModuleName]
-  deriving (Show, Read, Eq, Ord, Typeable, Data, Generic)
+  deriving (Show, Read, Eq, Ord, Data, Generic)
 
 -- | Interpret a 'ModuleRenaming' as a partial map from 'ModuleName'
 -- to 'ModuleName'.  For efficiency, you should partially apply it
diff --git a/Cabal-syntax/src/Distribution/Types/MungedPackageId.hs b/Cabal-syntax/src/Distribution/Types/MungedPackageId.hs
index f1e0904586d53b640f97122d4cbc0e166bc6ed9f..8e879620478fe8566339fa652d9d5ab4b0a67c96 100644
--- a/Cabal-syntax/src/Distribution/Types/MungedPackageId.hs
+++ b/Cabal-syntax/src/Distribution/Types/MungedPackageId.hs
@@ -28,7 +28,7 @@ data MungedPackageId = MungedPackageId
   , mungedVersion :: Version
   -- ^ The version of this package / component, eg 1.2
   }
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 instance Binary MungedPackageId
 instance Structured MungedPackageId
diff --git a/Cabal-syntax/src/Distribution/Types/MungedPackageName.hs b/Cabal-syntax/src/Distribution/Types/MungedPackageName.hs
index 78b648993d4b9538a13665e0227d7de58565e1e3..25a0f055362bfb9587a63a9b315d2e9cf0813d8b 100644
--- a/Cabal-syntax/src/Distribution/Types/MungedPackageName.hs
+++ b/Cabal-syntax/src/Distribution/Types/MungedPackageName.hs
@@ -31,7 +31,7 @@ import qualified Text.PrettyPrint as Disp
 --
 -- @since 2.0.0.2
 data MungedPackageName = MungedPackageName !PackageName !LibraryName
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 instance Binary MungedPackageName
 instance Structured MungedPackageName
diff --git a/Cabal-syntax/src/Distribution/Types/PackageDescription.hs b/Cabal-syntax/src/Distribution/Types/PackageDescription.hs
index 5e64694ac1f686f70e62620b0126e8786a86c0e3..4b00a8ef526acab08856078734af8657c08c1e34 100644
--- a/Cabal-syntax/src/Distribution/Types/PackageDescription.hs
+++ b/Cabal-syntax/src/Distribution/Types/PackageDescription.hs
@@ -151,7 +151,7 @@ data PackageDescription = PackageDescription
   , extraDocFiles :: [RelativePath Pkg File]
   , extraFiles :: [RelativePath Pkg File]
   }
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance Binary PackageDescription
 instance Structured PackageDescription
diff --git a/Cabal-syntax/src/Distribution/Types/PackageId.hs b/Cabal-syntax/src/Distribution/Types/PackageId.hs
index b5c4764ad22627186fcce72336e7ab116529f59a..9cd88a2f810529b6ede8882db8dc4d00d3f7bb4f 100644
--- a/Cabal-syntax/src/Distribution/Types/PackageId.hs
+++ b/Cabal-syntax/src/Distribution/Types/PackageId.hs
@@ -28,7 +28,7 @@ data PackageIdentifier = PackageIdentifier
   , pkgVersion :: Version
   -- ^ the version of this package, eg 1.2
   }
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 instance Binary PackageIdentifier
 instance Structured PackageIdentifier
diff --git a/Cabal-syntax/src/Distribution/Types/PackageName.hs b/Cabal-syntax/src/Distribution/Types/PackageName.hs
index 7bac16449a1ec8651bfccdf08deb228482e5d536..8a22662d672625ae42930e824fd06e35304d7200 100644
--- a/Cabal-syntax/src/Distribution/Types/PackageName.hs
+++ b/Cabal-syntax/src/Distribution/Types/PackageName.hs
@@ -26,7 +26,7 @@ import qualified Text.PrettyPrint as Disp
 --
 -- @since 2.0.0.2
 newtype PackageName = PackageName ShortText
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 -- | Convert 'PackageName' to 'String'
 unPackageName :: PackageName -> String
diff --git a/Cabal-syntax/src/Distribution/Types/PackageVersionConstraint.hs b/Cabal-syntax/src/Distribution/Types/PackageVersionConstraint.hs
index 9c328378d07cac1368c418c55a530ef47f3c09c1..013226ca2d527a68fd190126f282f8698240e725 100644
--- a/Cabal-syntax/src/Distribution/Types/PackageVersionConstraint.hs
+++ b/Cabal-syntax/src/Distribution/Types/PackageVersionConstraint.hs
@@ -26,7 +26,7 @@ import qualified Distribution.Compat.CharParsing as P
 -- There are a few places in the codebase where 'Dependency' was used where
 -- 'PackageVersionConstraint' is not used instead (#5570).
 data PackageVersionConstraint = PackageVersionConstraint PackageName VersionRange
-  deriving (Generic, Read, Show, Eq, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Data)
 
 instance Binary PackageVersionConstraint
 instance Structured PackageVersionConstraint
diff --git a/Cabal-syntax/src/Distribution/Types/PkgconfigDependency.hs b/Cabal-syntax/src/Distribution/Types/PkgconfigDependency.hs
index 695d3a3a184d1c6a25016f109360808a243ee1b3..54c8da7f66d540282fb50d3060b01012a0e75253 100644
--- a/Cabal-syntax/src/Distribution/Types/PkgconfigDependency.hs
+++ b/Cabal-syntax/src/Distribution/Types/PkgconfigDependency.hs
@@ -23,7 +23,7 @@ data PkgconfigDependency
   = PkgconfigDependency
       PkgconfigName
       PkgconfigVersionRange
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 instance Binary PkgconfigDependency
 instance Structured PkgconfigDependency
diff --git a/Cabal-syntax/src/Distribution/Types/PkgconfigName.hs b/Cabal-syntax/src/Distribution/Types/PkgconfigName.hs
index 7451b38e9da0d75c5d8cfc43d6310c2cea71075e..0057a9476142af8863843bb60be5d5451c449fc7 100644
--- a/Cabal-syntax/src/Distribution/Types/PkgconfigName.hs
+++ b/Cabal-syntax/src/Distribution/Types/PkgconfigName.hs
@@ -23,7 +23,7 @@ import qualified Text.PrettyPrint as Disp
 --
 -- @since 2.0.0.2
 newtype PkgconfigName = PkgconfigName ShortText
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 -- | Convert 'PkgconfigName' to 'String'
 --
diff --git a/Cabal-syntax/src/Distribution/Types/PkgconfigVersion.hs b/Cabal-syntax/src/Distribution/Types/PkgconfigVersion.hs
index dc328c44ddaa7743dcf366e177ce37ab6e787a73..d8db5b39bad3d9620c64aa15fcd87be0df2093f9 100644
--- a/Cabal-syntax/src/Distribution/Types/PkgconfigVersion.hs
+++ b/Cabal-syntax/src/Distribution/Types/PkgconfigVersion.hs
@@ -26,7 +26,7 @@ import qualified Text.PrettyPrint as PP
 --
 -- @since 3.0
 newtype PkgconfigVersion = PkgconfigVersion BS.ByteString
-  deriving (Generic, Read, Show, Typeable, Data)
+  deriving (Generic, Read, Show, Data)
 
 instance Eq PkgconfigVersion where
   PkgconfigVersion a == PkgconfigVersion b = rpmvercmp a b == EQ
diff --git a/Cabal-syntax/src/Distribution/Types/PkgconfigVersionRange.hs b/Cabal-syntax/src/Distribution/Types/PkgconfigVersionRange.hs
index fe74f70c7bef39632240a7b626ee145623e35beb..0699768409e8b4df3329b1c033d5bb96640081f2 100644
--- a/Cabal-syntax/src/Distribution/Types/PkgconfigVersionRange.hs
+++ b/Cabal-syntax/src/Distribution/Types/PkgconfigVersionRange.hs
@@ -37,7 +37,7 @@ data PkgconfigVersionRange
   | PcOrEarlierVersion PkgconfigVersion -- =< version
   | PcUnionVersionRanges PkgconfigVersionRange PkgconfigVersionRange
   | PcIntersectVersionRanges PkgconfigVersionRange PkgconfigVersionRange
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
+  deriving (Generic, Read, Show, Eq, Ord, Data)
 
 instance Binary PkgconfigVersionRange
 instance Structured PkgconfigVersionRange
diff --git a/Cabal-syntax/src/Distribution/Types/SetupBuildInfo.hs b/Cabal-syntax/src/Distribution/Types/SetupBuildInfo.hs
index 18a01523a9e77cb4fe95117835eb19c316deb73d..9feffbf71e698d23e4ec8dfe3c3e84cc13cb642b 100644
--- a/Cabal-syntax/src/Distribution/Types/SetupBuildInfo.hs
+++ b/Cabal-syntax/src/Distribution/Types/SetupBuildInfo.hs
@@ -25,7 +25,7 @@ data SetupBuildInfo = SetupBuildInfo
   -- internally, and doesn't correspond to anything in the .cabal
   -- file. See #3199.
   }
-  deriving (Generic, Show, Eq, Ord, Read, Typeable, Data)
+  deriving (Generic, Show, Eq, Ord, Read, Data)
 
 instance Binary SetupBuildInfo
 instance Structured SetupBuildInfo
diff --git a/Cabal-syntax/src/Distribution/Types/SourceRepo.hs b/Cabal-syntax/src/Distribution/Types/SourceRepo.hs
index 16a0fc60e0e0c707ed10a3c6a8889a5a81abc8c3..10ab9c16e635d0428457cfe0e202f0cd8bc102e7 100644
--- a/Cabal-syntax/src/Distribution/Types/SourceRepo.hs
+++ b/Cabal-syntax/src/Distribution/Types/SourceRepo.hs
@@ -77,7 +77,7 @@ data SourceRepo = SourceRepo
   -- relative to the root of the repository. This field is optional. If not
   -- given the default is \".\" ie no subdirectory.
   }
-  deriving (Eq, Ord, Generic, Read, Show, Typeable, Data)
+  deriving (Eq, Ord, Generic, Read, Show, Data)
 
 emptySourceRepo :: RepoKind -> SourceRepo
 emptySourceRepo kind =
@@ -106,7 +106,7 @@ data RepoKind
     -- information to re-create the exact sources.
     RepoThis
   | RepoKindUnknown String
-  deriving (Eq, Generic, Ord, Read, Show, Typeable, Data)
+  deriving (Eq, Generic, Ord, Read, Show, Data)
 
 instance Binary RepoKind
 instance Structured RepoKind
@@ -126,7 +126,7 @@ data KnownRepoType
   | Monotone
   | -- | @since 3.4.0.0
     Pijul
-  deriving (Eq, Generic, Ord, Read, Show, Typeable, Data, Enum, Bounded)
+  deriving (Eq, Generic, Ord, Read, Show, Data, Enum, Bounded)
 
 instance Binary KnownRepoType
 instance Structured KnownRepoType
@@ -146,7 +146,7 @@ instance Pretty KnownRepoType where
 data RepoType
   = KnownRepoType KnownRepoType
   | OtherRepoType String
-  deriving (Eq, Generic, Ord, Read, Show, Typeable, Data)
+  deriving (Eq, Generic, Ord, Read, Show, Data)
 
 instance Binary RepoType
 instance Structured RepoType
diff --git a/Cabal-syntax/src/Distribution/Types/TestSuite.hs b/Cabal-syntax/src/Distribution/Types/TestSuite.hs
index 6b3107cae7191c68c09985aec050cd3c21cce1a8..129e17dabfb61c1fdc116cbda2d6203b9cf217f7 100644
--- a/Cabal-syntax/src/Distribution/Types/TestSuite.hs
+++ b/Cabal-syntax/src/Distribution/Types/TestSuite.hs
@@ -28,7 +28,7 @@ data TestSuite = TestSuite
   , testBuildInfo :: BuildInfo
   , testCodeGenerators :: [String]
   }
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance L.HasBuildInfo TestSuite where
   buildInfo f l = (\x -> l{testBuildInfo = x}) <$> f (testBuildInfo l)
diff --git a/Cabal-syntax/src/Distribution/Types/TestSuiteInterface.hs b/Cabal-syntax/src/Distribution/Types/TestSuiteInterface.hs
index 37e87155e48fe3d2ca1955e2b5d633ca6a968d51..a64d2f61f6247891e5d1af29afa4472833a3ea34 100644
--- a/Cabal-syntax/src/Distribution/Types/TestSuiteInterface.hs
+++ b/Cabal-syntax/src/Distribution/Types/TestSuiteInterface.hs
@@ -30,7 +30,7 @@ data TestSuiteInterface
   | -- | A test suite that does not conform to one of the above interfaces for
     -- the given reason (e.g. unknown test type).
     TestSuiteUnsupported TestType
-  deriving (Eq, Ord, Generic, Read, Show, Typeable, Data)
+  deriving (Eq, Ord, Generic, Read, Show, Data)
 
 instance Binary TestSuiteInterface
 instance Structured TestSuiteInterface
diff --git a/Cabal-syntax/src/Distribution/Types/TestType.hs b/Cabal-syntax/src/Distribution/Types/TestType.hs
index 6ac0866d6f1452bec405d6c31731a308a1c65a23..88d3b3892f8b143e8728b86e50fdda046c370146 100644
--- a/Cabal-syntax/src/Distribution/Types/TestType.hs
+++ b/Cabal-syntax/src/Distribution/Types/TestType.hs
@@ -25,7 +25,7 @@ data TestType
     TestTypeLib Version
   | -- | Some unknown test type e.g. \"type: foo\"
     TestTypeUnknown String Version
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance Binary TestType
 instance Structured TestType
diff --git a/Cabal-syntax/src/Distribution/Types/UnitId.hs b/Cabal-syntax/src/Distribution/Types/UnitId.hs
index 36a1d003b2e1fb31b6e01686488f2b2d7bf91e70..0b5ca4bdf7b9e0065343a45c3193f92eb042a285 100644
--- a/Cabal-syntax/src/Distribution/Types/UnitId.hs
+++ b/Cabal-syntax/src/Distribution/Types/UnitId.hs
@@ -64,7 +64,7 @@ import Text.PrettyPrint (text)
 -- flag, use the 'display' function, which will work on all
 -- versions of Cabal.
 newtype UnitId = UnitId ShortText
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data, NFData)
+  deriving (Generic, Read, Show, Eq, Ord, Data, NFData)
 
 instance Binary UnitId
 instance Structured UnitId
@@ -118,7 +118,7 @@ getHSLibraryName uid = "HS" ++ prettyShow uid
 -- that a 'UnitId' identified this way is definite; i.e., it has no
 -- unfilled holes.
 newtype DefUnitId = DefUnitId {unDefUnitId :: UnitId}
-  deriving (Generic, Read, Show, Eq, Ord, Typeable, Data, Binary, NFData, Pretty)
+  deriving (Generic, Read, Show, Eq, Ord, Data, Binary, NFData, Pretty)
 
 instance Structured DefUnitId
 
diff --git a/Cabal-syntax/src/Distribution/Types/UnqualComponentName.hs b/Cabal-syntax/src/Distribution/Types/UnqualComponentName.hs
index 3879cdd2169e888f8aa765ff21dd58e9bd1f2726..f671759b42f7af31e37735361b1621a7667c1871 100644
--- a/Cabal-syntax/src/Distribution/Types/UnqualComponentName.hs
+++ b/Cabal-syntax/src/Distribution/Types/UnqualComponentName.hs
@@ -33,7 +33,6 @@ newtype UnqualComponentName = UnqualComponentName ShortText
     , Show
     , Eq
     , Ord
-    , Typeable
     , Data
     , Semigroup
     , Monoid -- TODO: bad enabler of bad monoids
diff --git a/Cabal-syntax/src/Distribution/Types/Version.hs b/Cabal-syntax/src/Distribution/Types/Version.hs
index 90ad33b1048528a8653dc5907d42dfc55082b3a9..efb2d497b49645d9302f2c7bb1a5fcf9d7a6f54a 100644
--- a/Cabal-syntax/src/Distribution/Types/Version.hs
+++ b/Cabal-syntax/src/Distribution/Types/Version.hs
@@ -47,7 +47,7 @@ data Version
   -- which all fall into the [0..0xfffe] range), then PV0
   -- MUST be used. This is essential for the 'Eq' instance
   -- to work.
-  deriving (Data, Eq, Generic, Typeable)
+  deriving (Data, Eq, Generic)
 
 instance Ord Version where
   compare (PV0 x) (PV0 y) = compare x y
diff --git a/Cabal-syntax/src/Distribution/Types/VersionInterval.hs b/Cabal-syntax/src/Distribution/Types/VersionInterval.hs
index efe04246cb8c8f87d9533bc7b8e79e23423d6e35..517c10491130c546baf3bb01d5563dfe50c1663a 100644
--- a/Cabal-syntax/src/Distribution/Types/VersionInterval.hs
+++ b/Cabal-syntax/src/Distribution/Types/VersionInterval.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE BangPatterns #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 
 -- | This module implements a view of a 'VersionRange' as a finite
 -- list of separated version intervals.
@@ -65,7 +64,7 @@ import Distribution.Types.VersionRange.Internal
 -- predicates for translation into foreign packaging systems that do not
 -- support complex version range expressions.
 newtype VersionIntervals = VersionIntervals [VersionInterval]
-  deriving (Eq, Show, Typeable)
+  deriving (Eq, Show)
 
 -- | Inspect the list of version intervals.
 unVersionIntervals :: VersionIntervals -> [VersionInterval]
diff --git a/Cabal-syntax/src/Distribution/Types/VersionInterval/Legacy.hs b/Cabal-syntax/src/Distribution/Types/VersionInterval/Legacy.hs
index f5e86d4a429d63d6e7101b2952ebc2679aa6bbe9..57e725b66d5393007c68414cbdf66df838802c53 100644
--- a/Cabal-syntax/src/Distribution/Types/VersionInterval/Legacy.hs
+++ b/Cabal-syntax/src/Distribution/Types/VersionInterval/Legacy.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
-
 -- | This module implements a view of a 'VersionRange' as a finite
 -- list of separated version intervals and provides the Boolean
 -- algebra operations union, intersection, and complement.
@@ -96,7 +94,7 @@ asVersionIntervals = versionIntervals . toVersionIntervals
 -- predicates for translation into foreign packaging systems that do not
 -- support complex version range expressions.
 newtype VersionIntervals = VersionIntervals [VersionInterval]
-  deriving (Eq, Show, Typeable)
+  deriving (Eq, Show)
 
 -- | Inspect the list of version intervals.
 versionIntervals :: VersionIntervals -> [VersionInterval]
diff --git a/Cabal-syntax/src/Distribution/Types/VersionRange/Internal.hs b/Cabal-syntax/src/Distribution/Types/VersionRange/Internal.hs
index ef82ae86045bd0aa4315477fd5effc8a29c67c75..8015dfa188f0d08da691a2f1470480f315e39d74 100644
--- a/Cabal-syntax/src/Distribution/Types/VersionRange/Internal.hs
+++ b/Cabal-syntax/src/Distribution/Types/VersionRange/Internal.hs
@@ -56,7 +56,7 @@ data VersionRange
   | MajorBoundVersion Version -- @^>= ver@ (same as >= ver && < MAJ(ver)+1)
   | UnionVersionRanges VersionRange VersionRange
   | IntersectVersionRanges VersionRange VersionRange
-  deriving (Data, Eq, Ord, Generic, Read, Show, Typeable)
+  deriving (Data, Eq, Ord, Generic, Read, Show)
 
 instance Binary VersionRange
 instance Structured VersionRange
@@ -179,7 +179,6 @@ data VersionRangeF a
     , Generic
     , Read
     , Show
-    , Typeable
     , Functor
     , Foldable
     , Traversable
diff --git a/Cabal-syntax/src/Distribution/Utils/Path.hs b/Cabal-syntax/src/Distribution/Utils/Path.hs
index 0e1c7c191e49d5d38088028fa6ec980455c860d5..a0f18a1dfdd9138b58f4bedbfb26a17ca628ba48 100644
--- a/Cabal-syntax/src/Distribution/Utils/Path.hs
+++ b/Cabal-syntax/src/Distribution/Utils/Path.hs
@@ -201,7 +201,7 @@ data AllowAbsolute
 -- until we interpret them (using e.g. 'interpretSymbolicPath').
 newtype SymbolicPathX (allowAbsolute :: AllowAbsolute) (from :: Type) (to :: FileOrDir)
   = SymbolicPath FilePath
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 type role SymbolicPathX nominal nominal nominal
 
diff --git a/Cabal-syntax/src/Distribution/Utils/ShortText.hs b/Cabal-syntax/src/Distribution/Utils/ShortText.hs
index 0b128de96983953d68ad6e2d810d339331a38afb..e1aa36ff236df244b961b813c56e3cb44bee64a1 100644
--- a/Cabal-syntax/src/Distribution/Utils/ShortText.hs
+++ b/Cabal-syntax/src/Distribution/Utils/ShortText.hs
@@ -93,7 +93,7 @@ null :: ShortText -> Bool
 -- @since 2.0.0.2
 #if HAVE_SHORTBYTESTRING
 newtype ShortText = ST { unST :: BS.Short.ShortByteString }
-                  deriving (Eq,Ord,Generic,Data,Typeable)
+                  deriving (Eq,Ord,Generic,Data)
 
 # if MIN_VERSION_binary(0,8,1)
 instance Binary ShortText where
@@ -115,7 +115,7 @@ unsafeFromUTF8BS = ST . BS.Short.toShort
 null = BS.Short.null . unST
 #else
 newtype ShortText = ST { unST :: String }
-                  deriving (Eq,Ord,Generic,Data,Typeable)
+                  deriving (Eq,Ord,Generic,Data)
 
 instance Binary ShortText where
     put = put . encodeStringUtf8 . unST
diff --git a/Cabal-syntax/src/Language/Haskell/Extension.hs b/Cabal-syntax/src/Language/Haskell/Extension.hs
index dce345605864d0914d39d6ad9a57a78d607a542b..c2a83f77acaecaf9f42d87c46325329998dd9e03 100644
--- a/Cabal-syntax/src/Language/Haskell/Extension.hs
+++ b/Cabal-syntax/src/Language/Haskell/Extension.hs
@@ -59,7 +59,7 @@ data Language
     GHC2024
   | -- | An unknown language, identified by its name.
     UnknownLanguage String
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance Binary Language
 instance Structured Language
@@ -115,7 +115,7 @@ data Extension
   | -- | An unknown extension, identified by the name of its @LANGUAGE@
     -- pragma.
     UnknownExtension String
-  deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Data)
 
 instance Binary Extension
 instance Structured Extension
@@ -556,7 +556,7 @@ data KnownExtension
   | -- | Allow use of or-pattern syntax, condensing multiple patterns
     -- into a single one.
     OrPatterns
-  deriving (Generic, Show, Read, Eq, Ord, Enum, Bounded, Typeable, Data)
+  deriving (Generic, Show, Read, Eq, Ord, Enum, Bounded, Data)
 
 instance Binary KnownExtension
 instance Structured KnownExtension
diff --git a/Cabal-tests/tests/UnitTests.hs b/Cabal-tests/tests/UnitTests.hs
index cc0099175a843db5bc334ece1bc97999ce986851..4c26e3e92a8507cff8688108c7ca901a298e371d 100644
--- a/Cabal-tests/tests/UnitTests.hs
+++ b/Cabal-tests/tests/UnitTests.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 module Main
     ( main
     ) where
@@ -7,7 +6,6 @@ import Test.Tasty
 import Test.Tasty.Options
 
 import Data.Proxy
-import Data.Typeable
 
 import Distribution.Simple.Utils
 import Distribution.Verbosity
@@ -90,7 +88,6 @@ extraOptions =
   ]
 
 newtype OptionMtimeChangeDelay = OptionMtimeChangeDelay Int
-  deriving Typeable
 
 instance IsOption OptionMtimeChangeDelay where
   defaultValue   = OptionMtimeChangeDelay 0
@@ -100,7 +97,6 @@ instance IsOption OptionMtimeChangeDelay where
                    ++ "file modification, in microseconds"
 
 newtype GhcPath = GhcPath FilePath
-  deriving Typeable
 
 instance IsOption GhcPath where
   defaultValue = GhcPath "ghc"
diff --git a/Cabal/src/Distribution/Backpack/ModuleShape.hs b/Cabal/src/Distribution/Backpack/ModuleShape.hs
index 039a6a30239a64269c5082e97851dff17040a4f8..aceb14d5bc41a24907a07cf32254c4ca75514611 100644
--- a/Cabal/src/Distribution/Backpack/ModuleShape.hs
+++ b/Cabal/src/Distribution/Backpack/ModuleShape.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 
 -- | See <https://github.com/ezyang/ghc-proposals/blob/backpack/proposals/0000-backpack.rst>
@@ -31,7 +30,7 @@ data ModuleShape = ModuleShape
   { modShapeProvides :: OpenModuleSubst
   , modShapeRequires :: Set ModuleName
   }
-  deriving (Eq, Show, Generic, Typeable)
+  deriving (Eq, Show, Generic)
 
 instance Binary ModuleShape
 instance Structured ModuleShape
diff --git a/Cabal/src/Distribution/Compat/Async.hs b/Cabal/src/Distribution/Compat/Async.hs
index b1234c8e346ead81acc4508c3dbe3b2f43e50a24..c0052b01185a59f32c8b42e6bc1f21dea13fac91 100644
--- a/Cabal/src/Distribution/Compat/Async.hs
+++ b/Cabal/src/Distribution/Compat/Async.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE CPP #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 
 -- | 'Async', yet using 'MVar's.
 --
@@ -40,7 +39,6 @@ import Control.Exception
   , uninterruptibleMask_
   )
 import Control.Monad (void)
-import Data.Typeable (Typeable)
 import GHC.Exts (inline)
 
 -- | Async, but based on 'MVar', as we don't depend on @stm@.
@@ -143,7 +141,6 @@ data AsyncCancelled = AsyncCancelled
   deriving
     ( Show
     , Eq
-    , Typeable
     )
 
 instance Exception AsyncCancelled where
diff --git a/Cabal/src/Distribution/Compat/Time.hs b/Cabal/src/Distribution/Compat/Time.hs
index 03d57449eb4f85898973df9e160bd55956a31398..088c01950c06973bc32820a5a5d43ed92f2c19f8 100644
--- a/Cabal/src/Distribution/Compat/Time.hs
+++ b/Cabal/src/Distribution/Compat/Time.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE CPP #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
@@ -55,7 +54,7 @@ import System.Posix.Files ( modificationTime )
 -- | An opaque type representing a file's modification time, represented
 -- internally as a 64-bit unsigned integer in the Windows UTC format.
 newtype ModTime = ModTime Word64
-  deriving (Binary, Generic, Bounded, Eq, Ord, Typeable)
+  deriving (Binary, Generic, Bounded, Eq, Ord)
 
 instance Structured ModTime
 
diff --git a/Cabal/src/Distribution/Simple/Compiler.hs b/Cabal/src/Distribution/Simple/Compiler.hs
index e93bec928400cefe36ac56286729bd082332217e..c24de7671722055989167b72b143e6931d96a861 100644
--- a/Cabal/src/Distribution/Simple/Compiler.hs
+++ b/Cabal/src/Distribution/Simple/Compiler.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE DeriveTraversable #-}
 
@@ -123,7 +122,7 @@ data Compiler = Compiler
   , compilerProperties :: Map String String
   -- ^ A key-value map for properties not covered by the above fields.
   }
-  deriving (Eq, Generic, Typeable, Show, Read)
+  deriving (Eq, Generic, Show, Read)
 
 instance Binary Compiler
 instance Structured Compiler
@@ -198,7 +197,7 @@ data PackageDBX fp
   | UserPackageDB
   | -- | NB: the path might be relative or it might be absolute
     SpecificPackageDB fp
-  deriving (Eq, Generic, Ord, Show, Read, Typeable, Functor, Foldable, Traversable)
+  deriving (Eq, Generic, Ord, Show, Read, Functor, Foldable, Traversable)
 
 instance Binary fp => Binary (PackageDBX fp)
 instance Structured fp => Structured (PackageDBX fp)
@@ -289,7 +288,7 @@ data OptimisationLevel
   = NoOptimisation
   | NormalOptimisation
   | MaximumOptimisation
-  deriving (Bounded, Enum, Eq, Generic, Read, Show, Typeable)
+  deriving (Bounded, Enum, Eq, Generic, Read, Show)
 
 instance Binary OptimisationLevel
 instance Structured OptimisationLevel
@@ -322,7 +321,7 @@ data DebugInfoLevel
   | MinimalDebugInfo
   | NormalDebugInfo
   | MaximalDebugInfo
-  deriving (Bounded, Enum, Eq, Generic, Read, Show, Typeable)
+  deriving (Bounded, Enum, Eq, Generic, Read, Show)
 
 instance Binary DebugInfoLevel
 instance Structured DebugInfoLevel
@@ -559,7 +558,7 @@ data ProfDetailLevel
   | ProfDetailAllFunctions
   | ProfDetailTopLate
   | ProfDetailOther String
-  deriving (Eq, Generic, Read, Show, Typeable)
+  deriving (Eq, Generic, Read, Show)
 
 instance Binary ProfDetailLevel
 instance Structured ProfDetailLevel
diff --git a/Cabal/src/Distribution/Simple/Configure.hs b/Cabal/src/Distribution/Simple/Configure.hs
index 9cea0fda39faddb4a99bb3fb7c88a6cf1cb6e404..7c96efb33fc69122acaa96dcad75d3181a18716a 100644
--- a/Cabal/src/Distribution/Simple/Configure.hs
+++ b/Cabal/src/Distribution/Simple/Configure.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE NamedFieldPuns #-}
 {-# LANGUAGE OverloadedStrings #-}
@@ -204,7 +203,6 @@ data ConfigStateFileError
       PackageIdentifier
       PackageIdentifier
       (Either ConfigStateFileError LocalBuildInfo)
-  deriving (Typeable)
 
 -- | Format a 'ConfigStateFileError' as a user-facing error message.
 dispConfigStateFileError :: ConfigStateFileError -> Doc
diff --git a/Cabal/src/Distribution/Simple/Errors.hs b/Cabal/src/Distribution/Simple/Errors.hs
index 791c7440538747056f0f3f047460566c5d2a348c..1ce4f7ca06a86584e7532f8589dbd9efb31ee302 100644
--- a/Cabal/src/Distribution/Simple/Errors.hs
+++ b/Cabal/src/Distribution/Simple/Errors.hs
@@ -171,7 +171,7 @@ data CabalException
   | UnknownVersionDb String VersionRange FilePath
   | MissingCoveredInstalledLibrary UnitId
   | SetupHooksException SetupHooksException
-  deriving (Show, Typeable)
+  deriving (Show)
 
 exceptionCode :: CabalException -> Int
 exceptionCode e = case e of
diff --git a/Cabal/src/Distribution/Simple/Flag.hs b/Cabal/src/Distribution/Simple/Flag.hs
index 35e7a9b9e7c3d4f7c0e27e37244752e45f01017e..744a7da1331521c1d6d399a93fab2cc50fdda30f 100644
--- a/Cabal/src/Distribution/Simple/Flag.hs
+++ b/Cabal/src/Distribution/Simple/Flag.hs
@@ -61,7 +61,7 @@ import Prelude ()
 -- 'NoFlag' and later flags override earlier ones.
 --
 -- Isomorphic to 'Maybe' a.
-data Flag a = Flag a | NoFlag deriving (Eq, Generic, Show, Read, Typeable, Foldable, Traversable)
+data Flag a = Flag a | NoFlag deriving (Eq, Generic, Show, Read, Foldable, Traversable)
 
 instance Binary a => Binary (Flag a)
 instance Structured a => Structured (Flag a)
diff --git a/Cabal/src/Distribution/Simple/GHC/EnvironmentParser.hs b/Cabal/src/Distribution/Simple/GHC/EnvironmentParser.hs
index 70a1ec64c578ccf38ed092b303ea5dc2bb36dd08..19981f51c3be172d874241bf5f7ee027fa487ed2 100644
--- a/Cabal/src/Distribution/Simple/GHC/EnvironmentParser.hs
+++ b/Cabal/src/Distribution/Simple/GHC/EnvironmentParser.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE RankNTypes #-}
 
@@ -41,7 +40,7 @@ parseEnvironmentFileLine =
     clearDb = P.string "clear-package-db"
 
 newtype ParseErrorExc = ParseErrorExc P.ParseError
-  deriving (Show, Typeable)
+  deriving (Show)
 
 instance Exception ParseErrorExc
 
diff --git a/Cabal/src/Distribution/Simple/InstallDirs.hs b/Cabal/src/Distribution/Simple/InstallDirs.hs
index b478aefe51152d61920b1455601d6ad66aada9ca..86e6fa08777bfb31924f6480e27a57ab292af52a 100644
--- a/Cabal/src/Distribution/Simple/InstallDirs.hs
+++ b/Cabal/src/Distribution/Simple/InstallDirs.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE CPP #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveFunctor #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
@@ -101,7 +100,7 @@ data InstallDirs dir = InstallDirs
   , haddockdir :: dir
   , sysconfdir :: dir
   }
-  deriving (Eq, Read, Show, Functor, Generic, Typeable)
+  deriving (Eq, Read, Show, Functor, Generic)
 
 instance Binary dir => Binary (InstallDirs dir)
 instance Structured dir => Structured (InstallDirs dir)
@@ -389,7 +388,7 @@ prefixRelativeInstallDirs pkgId libname compilerId platform dirs =
 -- | An abstract path, possibly containing variables that need to be
 -- substituted for to get a real 'FilePath'.
 newtype PathTemplate = PathTemplate [PathComponent]
-  deriving (Eq, Ord, Generic, Typeable)
+  deriving (Eq, Ord, Generic)
 
 instance Binary PathTemplate
 instance Structured PathTemplate
diff --git a/Cabal/src/Distribution/Simple/InstallDirs/Internal.hs b/Cabal/src/Distribution/Simple/InstallDirs/Internal.hs
index 9c411b7dcc15740cbb458c14d821f4e67a0d9e8c..a65c706af207d15597a4b7988abb949f04f54941 100644
--- a/Cabal/src/Distribution/Simple/InstallDirs/Internal.hs
+++ b/Cabal/src/Distribution/Simple/InstallDirs/Internal.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 
 module Distribution.Simple.InstallDirs.Internal
@@ -12,7 +11,7 @@ import Prelude ()
 data PathComponent
   = Ordinary FilePath
   | Variable PathTemplateVariable
-  deriving (Eq, Ord, Generic, Typeable)
+  deriving (Eq, Ord, Generic)
 
 instance Binary PathComponent
 instance Structured PathComponent
@@ -65,7 +64,7 @@ data PathTemplateVariable
     TestSuiteResultVar
   | -- | The name of the benchmark being run
     BenchmarkNameVar
-  deriving (Eq, Ord, Generic, Typeable)
+  deriving (Eq, Ord, Generic)
 
 instance Binary PathTemplateVariable
 instance Structured PathTemplateVariable
diff --git a/Cabal/src/Distribution/Simple/PackageIndex.hs b/Cabal/src/Distribution/Simple/PackageIndex.hs
index e6944430755b7266d5ba6c20d949a9370042eced..a7d23962b7217e3d4c2cc57b5246979ce2d56014 100644
--- a/Cabal/src/Distribution/Simple/PackageIndex.hs
+++ b/Cabal/src/Distribution/Simple/PackageIndex.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE FlexibleInstances #-}
@@ -147,7 +146,7 @@ data PackageIndex a = PackageIndex
     -- preserved. See #1463 for discussion.
     packageIdIndex :: !(Map (PackageName, LibraryName) (Map Version [a]))
   }
-  deriving (Eq, Generic, Show, Read, Typeable)
+  deriving (Eq, Generic, Show, Read)
 
 instance Binary a => Binary (PackageIndex a)
 instance Structured a => Structured (PackageIndex a)
diff --git a/Cabal/src/Distribution/Simple/Program/Db.hs b/Cabal/src/Distribution/Simple/Program/Db.hs
index a9aefa7d649064f5dccc60e7921d481c52f7a1ba..c76b38e9923855a5e6dc6cd2c2bbe09a521c32fb 100644
--- a/Cabal/src/Distribution/Simple/Program/Db.hs
+++ b/Cabal/src/Distribution/Simple/Program/Db.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE RankNTypes #-}
 
@@ -106,7 +105,6 @@ data ProgramDb = ProgramDb
   , progOverrideEnv :: [(String, Maybe String)]
   , configuredProgs :: ConfiguredProgs
   }
-  deriving (Typeable)
 
 type UnconfiguredProgram = (Program, Maybe FilePath, [ProgArg])
 type UnconfiguredProgs = Map.Map String UnconfiguredProgram
diff --git a/Cabal/src/Distribution/Simple/Program/Types.hs b/Cabal/src/Distribution/Simple/Program/Types.hs
index 3b03f6353cfe92b735d35d5c4b290f4a611a4805..bcbd05c520dd3918d774ccb1c8d040cdc8922576 100644
--- a/Cabal/src/Distribution/Simple/Program/Types.hs
+++ b/Cabal/src/Distribution/Simple/Program/Types.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE RankNTypes #-}
@@ -107,7 +106,7 @@ data ProgramSearchPathEntry
     ProgramSearchPathDir FilePath
   | -- | The system default
     ProgramSearchPathDefault
-  deriving (Show, Eq, Generic, Typeable)
+  deriving (Show, Eq, Generic)
 
 instance Binary ProgramSearchPathEntry
 instance Structured ProgramSearchPathEntry
@@ -147,7 +146,7 @@ data ConfiguredProgram = ConfiguredProgram
   -- monitor to detect when the re-configuring the program might give a
   -- different result (e.g. found in a different location).
   }
-  deriving (Eq, Generic, Read, Show, Typeable)
+  deriving (Eq, Generic, Read, Show)
 
 instance Binary ConfiguredProgram
 instance Structured ConfiguredProgram
@@ -160,7 +159,7 @@ data ProgramLocation
     UserSpecified {locationPath :: FilePath}
   | -- | The program was found automatically.
     FoundOnSystem {locationPath :: FilePath}
-  deriving (Eq, Generic, Read, Show, Typeable)
+  deriving (Eq, Generic, Read, Show)
 
 instance Binary ProgramLocation
 instance Structured ProgramLocation
diff --git a/Cabal/src/Distribution/Simple/Setup/Benchmark.hs b/Cabal/src/Distribution/Simple/Setup/Benchmark.hs
index 36fc446b5a183ae6d56dd338f9b09d5daf63f628..a46073ba4347c5c5632ce50e3752262e2d99b28f 100644
--- a/Cabal/src/Distribution/Simple/Setup/Benchmark.hs
+++ b/Cabal/src/Distribution/Simple/Setup/Benchmark.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE PatternSynonyms #-}
@@ -56,7 +55,7 @@ data BenchmarkFlags = BenchmarkFlags
   { benchmarkCommonFlags :: !CommonSetupFlags
   , benchmarkOptions :: [PathTemplate]
   }
-  deriving (Show, Generic, Typeable)
+  deriving (Show, Generic)
 
 pattern BenchmarkCommonFlags
   :: Flag Verbosity
diff --git a/Cabal/src/Distribution/Simple/Setup/Build.hs b/Cabal/src/Distribution/Simple/Setup/Build.hs
index 09aad42bdc8535d340b0d2d875466bf108369bee..c0aedc25bd0feb69f0ac8dd8e4b712c43e8b1047 100644
--- a/Cabal/src/Distribution/Simple/Setup/Build.hs
+++ b/Cabal/src/Distribution/Simple/Setup/Build.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE PatternSynonyms #-}
@@ -62,7 +61,7 @@ data BuildFlags = BuildFlags
   , buildNumJobs :: Flag (Maybe Int)
   , buildUseSemaphore :: Flag String
   }
-  deriving (Read, Show, Generic, Typeable)
+  deriving (Read, Show, Generic)
 
 pattern BuildCommonFlags
   :: Flag Verbosity
diff --git a/Cabal/src/Distribution/Simple/Setup/Clean.hs b/Cabal/src/Distribution/Simple/Setup/Clean.hs
index 6a1974f323e37e4cfe7d7ff35ca72d8bef45f121..8700e32b4a39a03f6221bf0daecafb06a6aa69e9 100644
--- a/Cabal/src/Distribution/Simple/Setup/Clean.hs
+++ b/Cabal/src/Distribution/Simple/Setup/Clean.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE PatternSynonyms #-}
@@ -54,7 +53,7 @@ data CleanFlags = CleanFlags
   { cleanCommonFlags :: !CommonSetupFlags
   , cleanSaveConf :: Flag Bool
   }
-  deriving (Show, Generic, Typeable)
+  deriving (Show, Generic)
 
 pattern CleanCommonFlags
   :: Flag Verbosity
diff --git a/Cabal/src/Distribution/Simple/Setup/Config.hs b/Cabal/src/Distribution/Simple/Setup/Config.hs
index 8369f4fc701cf859625e1d600ebd790f9f877ffb..c904ecf2b44e898d9cf3a31974fb6a833d81f16f 100644
--- a/Cabal/src/Distribution/Simple/Setup/Config.hs
+++ b/Cabal/src/Distribution/Simple/Setup/Config.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE PatternSynonyms #-}
@@ -235,7 +234,7 @@ data ConfigFlags = ConfigFlags
   -- `build-tool-depends` will be ignored. This allows a Cabal package with
   -- build-tool-dependencies to be built even if the tool is not found.
   }
-  deriving (Generic, Read, Show, Typeable)
+  deriving (Generic, Read, Show)
 
 pattern ConfigCommonFlags
   :: Flag Verbosity
diff --git a/Cabal/src/Distribution/Simple/Setup/Global.hs b/Cabal/src/Distribution/Simple/Setup/Global.hs
index b230289446dbcd19a6424d67722ea27bcc729dff..540edab97834dc555c1d7aa741f4fe981ce6d919 100644
--- a/Cabal/src/Distribution/Simple/Setup/Global.hs
+++ b/Cabal/src/Distribution/Simple/Setup/Global.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE RankNTypes #-}
@@ -51,7 +50,7 @@ data GlobalFlags = GlobalFlags
   , globalNumericVersion :: Flag Bool
   , globalWorkingDir :: Flag (SymbolicPath CWD (Dir Pkg))
   }
-  deriving (Generic, Typeable)
+  deriving (Generic)
 
 defaultGlobalFlags :: GlobalFlags
 defaultGlobalFlags =
diff --git a/Cabal/src/Distribution/Simple/Setup/Haddock.hs b/Cabal/src/Distribution/Simple/Setup/Haddock.hs
index 6f0459b73110abad4c425317cb756606a6ee7d7a..f16faf248e91c18d44de418022a63d4c37d14f32 100644
--- a/Cabal/src/Distribution/Simple/Setup/Haddock.hs
+++ b/Cabal/src/Distribution/Simple/Setup/Haddock.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE PatternSynonyms #-}
@@ -76,7 +75,7 @@ import qualified Text.PrettyPrint as Disp
 --    from documentation tarballs, and we might also want to use different
 --    flags than for development builds, so in this case we store the generated
 --    documentation in @<dist>/doc/html/<package id>-docs@.
-data HaddockTarget = ForHackage | ForDevelopment deriving (Eq, Show, Generic, Typeable)
+data HaddockTarget = ForHackage | ForDevelopment deriving (Eq, Show, Generic)
 
 instance Binary HaddockTarget
 instance Structured HaddockTarget
@@ -116,7 +115,7 @@ data HaddockFlags = HaddockFlags
   , haddockOutputDir :: Flag FilePath
   , haddockUseUnicode :: Flag Bool
   }
-  deriving (Show, Generic, Typeable)
+  deriving (Show, Generic)
 
 pattern HaddockCommonFlags
   :: Flag Verbosity
@@ -442,7 +441,7 @@ data HaddockProjectFlags = HaddockProjectFlags
     haddockProjectResourcesDir :: Flag String
   , haddockProjectUseUnicode :: Flag Bool
   }
-  deriving (Show, Generic, Typeable)
+  deriving (Show, Generic)
 
 defaultHaddockProjectFlags :: HaddockProjectFlags
 defaultHaddockProjectFlags =
diff --git a/Cabal/src/Distribution/Simple/Setup/Hscolour.hs b/Cabal/src/Distribution/Simple/Setup/Hscolour.hs
index 1c62c2dedca03a479f866e0d3f4ebab35ca0058b..56632d5d2f70fe15246f671bcae1744c6f2a2ebe 100644
--- a/Cabal/src/Distribution/Simple/Setup/Hscolour.hs
+++ b/Cabal/src/Distribution/Simple/Setup/Hscolour.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE PatternSynonyms #-}
@@ -58,7 +57,7 @@ data HscolourFlags = HscolourFlags
   , hscolourBenchmarks :: Flag Bool
   , hscolourForeignLibs :: Flag Bool
   }
-  deriving (Show, Generic, Typeable)
+  deriving (Show, Generic)
 
 pattern HscolourCommonFlags
   :: Flag Verbosity
diff --git a/Cabal/src/Distribution/Simple/Setup/Register.hs b/Cabal/src/Distribution/Simple/Setup/Register.hs
index bbd179322455295b9be64fadf52fdc15bb451f7a..f7b9e80e007951477784a3ec756b865ea31abfea 100644
--- a/Cabal/src/Distribution/Simple/Setup/Register.hs
+++ b/Cabal/src/Distribution/Simple/Setup/Register.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE PatternSynonyms #-}
@@ -62,7 +61,7 @@ data RegisterFlags = RegisterFlags
   , regInPlace :: Flag Bool
   , regPrintId :: Flag Bool
   }
-  deriving (Show, Generic, Typeable)
+  deriving (Show, Generic)
 
 pattern RegisterCommonFlags
   :: Flag Verbosity
diff --git a/Cabal/src/Distribution/Simple/Setup/Repl.hs b/Cabal/src/Distribution/Simple/Setup/Repl.hs
index 7d53ca33668975b0065712a2d6332225f96fae1e..fbe15df56eb1f574b14af179f38880ad9407832d 100644
--- a/Cabal/src/Distribution/Simple/Setup/Repl.hs
+++ b/Cabal/src/Distribution/Simple/Setup/Repl.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE PatternSynonyms #-}
@@ -59,7 +58,7 @@ data ReplOptions = ReplOptions
   , replOptionsNoLoad :: Flag Bool
   , replOptionsFlagOutput :: Flag FilePath
   }
-  deriving (Show, Generic, Typeable)
+  deriving (Show, Generic)
 
 pattern ReplCommonFlags
   :: Flag Verbosity
@@ -102,7 +101,7 @@ data ReplFlags = ReplFlags
   , replReload :: Flag Bool
   , replReplOptions :: ReplOptions
   }
-  deriving (Show, Generic, Typeable)
+  deriving (Show, Generic)
 
 instance Binary ReplFlags
 instance Structured ReplFlags
diff --git a/Cabal/src/Distribution/Simple/Setup/SDist.hs b/Cabal/src/Distribution/Simple/Setup/SDist.hs
index 6caf8e51e52c7e84e126cb5b3e8483fb52bb506e..218d1e9f20903254cacf7919c73dc8ecc9381282 100644
--- a/Cabal/src/Distribution/Simple/Setup/SDist.hs
+++ b/Cabal/src/Distribution/Simple/Setup/SDist.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE PatternSynonyms #-}
@@ -57,7 +56,7 @@ data SDistFlags = SDistFlags
   , sDistDirectory :: Flag FilePath
   , sDistListSources :: Flag FilePath
   }
-  deriving (Show, Generic, Typeable)
+  deriving (Show, Generic)
 
 pattern SDistCommonFlags
   :: Flag Verbosity
diff --git a/Cabal/src/Distribution/Simple/Setup/Test.hs b/Cabal/src/Distribution/Simple/Setup/Test.hs
index e4c2706eed6c037bf81ba68869caaaa24c1fc471..45f77c938e00c8e46f45023e1142b1c332575885 100644
--- a/Cabal/src/Distribution/Simple/Setup/Test.hs
+++ b/Cabal/src/Distribution/Simple/Setup/Test.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE PatternSynonyms #-}
@@ -61,7 +60,7 @@ import qualified Text.PrettyPrint as Disp
 -- ------------------------------------------------------------
 
 data TestShowDetails = Never | Failures | Always | Streaming | Direct
-  deriving (Eq, Ord, Enum, Bounded, Generic, Show, Typeable)
+  deriving (Eq, Ord, Enum, Bounded, Generic, Show)
 
 instance Binary TestShowDetails
 instance Structured TestShowDetails
@@ -102,7 +101,7 @@ data TestFlags = TestFlags
   , -- TODO: think about if/how options are passed to test exes
     testOptions :: [PathTemplate]
   }
-  deriving (Show, Generic, Typeable)
+  deriving (Show, Generic)
 
 pattern TestCommonFlags
   :: Flag Verbosity
diff --git a/Cabal/src/Distribution/Simple/Utils.hs b/Cabal/src/Distribution/Simple/Utils.hs
index b54763d4a251dd1d1eddc0c34bfa5d7f0ee984e6..bdbb72435a3386fc64e4d87fdde95b0e163b1c70 100644
--- a/Cabal/src/Distribution/Simple/Utils.hs
+++ b/Cabal/src/Distribution/Simple/Utils.hs
@@ -424,7 +424,7 @@ die' verbosity msg = withFrozenCallStack $ do
 
 -- Type which will be a wrapper for cabal -exceptions and cabal-install exceptions
 data VerboseException a = VerboseException CallStack POSIXTime Verbosity a
-  deriving (Show, Typeable)
+  deriving (Show)
 
 -- Function which will replace the existing die' call sites
 dieWithException :: (HasCallStack, Show a1, Typeable a1, Exception (VerboseException a1)) => Verbosity -> a1 -> IO a
diff --git a/Cabal/src/Distribution/Types/ComponentLocalBuildInfo.hs b/Cabal/src/Distribution/Types/ComponentLocalBuildInfo.hs
index 9e63cae52ea7f33e31b242b0834157028bdacc54..32f4aab473b139a8de927b2d2eab3e4d221a693a 100644
--- a/Cabal/src/Distribution/Types/ComponentLocalBuildInfo.hs
+++ b/Cabal/src/Distribution/Types/ComponentLocalBuildInfo.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE TypeFamilies #-}
 
@@ -110,7 +109,7 @@ data ComponentLocalBuildInfo
       , componentExeDeps :: [UnitId]
       , componentInternalDeps :: [UnitId]
       }
-  deriving (Generic, Read, Show, Typeable)
+  deriving (Generic, Read, Show)
 
 instance Binary ComponentLocalBuildInfo
 instance Structured ComponentLocalBuildInfo
diff --git a/Cabal/src/Distribution/Types/DumpBuildInfo.hs b/Cabal/src/Distribution/Types/DumpBuildInfo.hs
index 2b3dae8888f94125e4eb6aec1cda994c685d8725..99020febc35f5b17700a5f9121ccddccea992bb0 100644
--- a/Cabal/src/Distribution/Types/DumpBuildInfo.hs
+++ b/Cabal/src/Distribution/Types/DumpBuildInfo.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 
 module Distribution.Types.DumpBuildInfo
@@ -10,7 +9,7 @@ import Distribution.Compat.Prelude
 data DumpBuildInfo
   = NoDumpBuildInfo
   | DumpBuildInfo
-  deriving (Read, Show, Eq, Ord, Enum, Bounded, Generic, Typeable)
+  deriving (Read, Show, Eq, Ord, Enum, Bounded, Generic)
 
 instance Binary DumpBuildInfo
 instance Structured DumpBuildInfo
diff --git a/Cabal/src/Distribution/Types/GivenComponent.hs b/Cabal/src/Distribution/Types/GivenComponent.hs
index 235c8c372a057d6665c2705d2c8bd233fe082a0d..c06fcbbfb4e47d822cabc79b617f713f8a629826 100644
--- a/Cabal/src/Distribution/Types/GivenComponent.hs
+++ b/Cabal/src/Distribution/Types/GivenComponent.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 
 module Distribution.Types.GivenComponent
@@ -25,7 +24,7 @@ data GivenComponent = GivenComponent
   -- only, not for any component
   , givenComponentId :: ComponentId
   }
-  deriving (Generic, Read, Show, Eq, Typeable)
+  deriving (Generic, Read, Show, Eq)
 
 instance Binary GivenComponent
 instance Structured GivenComponent
@@ -42,7 +41,7 @@ data PromisedComponent = PromisedComponent
   -- only, not for any component
   , promisedComponentId :: ComponentId
   }
-  deriving (Generic, Read, Show, Eq, Typeable)
+  deriving (Generic, Read, Show, Eq)
 
 instance Binary PromisedComponent
 instance Structured PromisedComponent
diff --git a/Cabal/src/Distribution/Types/LocalBuildInfo.hs b/Cabal/src/Distribution/Types/LocalBuildInfo.hs
index 7bfb1be5926fb72be3ca4df3b33a50d185ea448d..854f454dc875cbf8229ddc358068bbb3fd653d7b 100644
--- a/Cabal/src/Distribution/Types/LocalBuildInfo.hs
+++ b/Cabal/src/Distribution/Types/LocalBuildInfo.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE DuplicateRecordFields #-}
 {-# LANGUAGE FlexibleContexts #-}
@@ -144,7 +143,7 @@ data LocalBuildInfo = NewLocalBuildInfo
   -- ^ Information about a package configuration
   -- that can be modified by the user at configuration time.
   }
-  deriving (Generic, Read, Show, Typeable)
+  deriving (Generic, Read, Show)
 
 {-# COMPLETE LocalBuildInfo #-}
 
diff --git a/Cabal/src/Distribution/Utils/NubList.hs b/Cabal/src/Distribution/Utils/NubList.hs
index 2a7e69a7a857f88f8cd218e505f864b1581fa2b5..09da19aa5ae40a3b51af5f8316b8c87f01a9d3bd 100644
--- a/Cabal/src/Distribution/Utils/NubList.hs
+++ b/Cabal/src/Distribution/Utils/NubList.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 
@@ -22,7 +21,7 @@ import qualified Text.Read as R
 
 -- | NubList : A de-duplicated list that maintains the original order.
 newtype NubList a = NubList {fromNubList :: [a]}
-  deriving (Eq, Generic, Typeable)
+  deriving (Eq, Generic)
 
 -- NubList assumes that nub retains the list order while removing duplicate
 -- elements (keeping the first occurrence). Documentation for "Data.List.nub"
diff --git a/Cabal/src/Distribution/Verbosity.hs b/Cabal/src/Distribution/Verbosity.hs
index bab48bbed2147b8b0a0337ddbe71cd39213d09e9..c81c6dd86304ab3eaab968d9b9d903397930ec9d 100644
--- a/Cabal/src/Distribution/Verbosity.hs
+++ b/Cabal/src/Distribution/Verbosity.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 
 -----------------------------------------------------------------------------
@@ -92,7 +91,7 @@ data Verbosity = Verbosity
   , vFlags :: Set VerbosityFlag
   , vQuiet :: Bool
   }
-  deriving (Generic, Show, Read, Typeable)
+  deriving (Generic, Show, Read)
 
 mkVerbosity :: VerbosityLevel -> Verbosity
 mkVerbosity l = Verbosity{vLevel = l, vFlags = Set.empty, vQuiet = False}
diff --git a/Cabal/src/Distribution/Verbosity/Internal.hs b/Cabal/src/Distribution/Verbosity/Internal.hs
index b8f55cf5b98e1323dd50e784069ffedc74caa65e..9d851f59f074b8df0abf86902e86d9ca2f4c3160 100644
--- a/Cabal/src/Distribution/Verbosity/Internal.hs
+++ b/Cabal/src/Distribution/Verbosity/Internal.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 
 module Distribution.Verbosity.Internal
@@ -10,7 +9,7 @@ import Distribution.Compat.Prelude
 import Prelude ()
 
 data VerbosityLevel = Silent | Normal | Verbose | Deafening
-  deriving (Generic, Show, Read, Eq, Ord, Enum, Bounded, Typeable)
+  deriving (Generic, Show, Read, Eq, Ord, Enum, Bounded)
 
 instance Binary VerbosityLevel
 instance Structured VerbosityLevel
@@ -24,7 +23,7 @@ data VerbosityFlag
   | -- | @since 3.4.0.0
     VStderr
   | VNoWarn
-  deriving (Generic, Show, Read, Eq, Ord, Enum, Bounded, Typeable)
+  deriving (Generic, Show, Read, Eq, Ord, Enum, Bounded)
 
 instance Binary VerbosityFlag
 instance Structured VerbosityFlag
diff --git a/cabal-install-solver/src/Distribution/Solver/Types/OptionalStanza.hs b/cabal-install-solver/src/Distribution/Solver/Types/OptionalStanza.hs
index cde029d195b8198656e4d24e935bc2c374f96c50..457cd6c9b1349362c42b5f68224d2c4f73114b3f 100644
--- a/cabal-install-solver/src/Distribution/Solver/Types/OptionalStanza.hs
+++ b/cabal-install-solver/src/Distribution/Solver/Types/OptionalStanza.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric      #-}
 module Distribution.Solver.Types.OptionalStanza (
     -- * OptionalStanza
@@ -38,7 +37,7 @@ import Distribution.Utils.Structured (Structured (..), nominalStructure)
 data OptionalStanza
     = TestStanzas
     | BenchStanzas
-  deriving (Eq, Ord, Enum, Bounded, Show, Generic, Typeable)
+  deriving (Eq, Ord, Enum, Bounded, Show, Generic)
 
 -- | String representation of an OptionalStanza.
 showStanza :: OptionalStanza -> String
diff --git a/cabal-install-solver/src/Distribution/Solver/Types/PkgConfigDb.hs b/cabal-install-solver/src/Distribution/Solver/Types/PkgConfigDb.hs
index 13322d00f65ead4a12dfe0a184761b8dffd6f1ab..6053fbf4f56d870289f4908c256b10c934699a3a 100644
--- a/cabal-install-solver/src/Distribution/Solver/Types/PkgConfigDb.hs
+++ b/cabal-install-solver/src/Distribution/Solver/Types/PkgConfigDb.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric      #-}
 -----------------------------------------------------------------------------
 -- |
@@ -52,7 +51,7 @@ import Distribution.Verbosity                   (Verbosity)
 -- but we don't know the exact version (because parsing of the version number
 -- failed).
 newtype PkgConfigDb = PkgConfigDb (M.Map PkgconfigName (Maybe PkgconfigVersion))
-     deriving (Show, Generic, Typeable)
+     deriving (Show, Generic)
 
 instance Binary PkgConfigDb
 instance Structured PkgConfigDb
diff --git a/cabal-install-solver/src/Distribution/Solver/Types/SourcePackage.hs b/cabal-install-solver/src/Distribution/Solver/Types/SourcePackage.hs
index 35cba9b6e4aef731bd9beece25edf08f56e93a25..0162f6e7f020b96f58a300fb059a0add993e4d4b 100644
--- a/cabal-install-solver/src/Distribution/Solver/Types/SourcePackage.hs
+++ b/cabal-install-solver/src/Distribution/Solver/Types/SourcePackage.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE DeriveGeneric #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 module Distribution.Solver.Types.SourcePackage
     ( PackageDescriptionOverride
     , SourcePackage(..)
@@ -25,7 +24,7 @@ data SourcePackage loc = SourcePackage
   , srcpkgSource        :: loc
   , srcpkgDescrOverride :: PackageDescriptionOverride
   }
-  deriving (Eq, Show, Generic, Typeable)
+  deriving (Eq, Show, Generic)
 
 instance Binary loc => Binary (SourcePackage loc)
 instance Structured loc => Structured (SourcePackage loc)
diff --git a/cabal-install/src/Distribution/Client/Compat/Semaphore.hs b/cabal-install/src/Distribution/Client/Compat/Semaphore.hs
index 42c398b5c33c8a92c691417de5f1dc50564d3026..60fda2cf389de211ccf4efd498cf733348ba826b 100644
--- a/cabal-install/src/Distribution/Client/Compat/Semaphore.hs
+++ b/cabal-install/src/Distribution/Client/Compat/Semaphore.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# OPTIONS_GHC -funbox-strict-fields #-}
 
 module Distribution.Client.Compat.Semaphore
@@ -22,13 +21,12 @@ import Control.Exception (mask_, onException)
 import Control.Monad (join, unless)
 import Data.List.NonEmpty (NonEmpty (..))
 import qualified Data.List.NonEmpty as NE
-import Data.Typeable (Typeable)
 
 -- | 'QSem' is a quantity semaphore in which the resource is acquired
 -- and released in units of one. It provides guaranteed FIFO ordering
 -- for satisfying blocked `waitQSem` calls.
 data QSem = QSem !(TVar Int) !(TVar [TVar Bool]) !(TVar [TVar Bool])
-  deriving (Eq, Typeable)
+  deriving (Eq)
 
 newQSem :: Int -> IO QSem
 newQSem i = atomically $ do
diff --git a/cabal-install/src/Distribution/Client/Errors.hs b/cabal-install/src/Distribution/Client/Errors.hs
index 3b80b50dd94ad814801a8c057839f74afa7357a9..0c242bcad1a35f728c8d3ecac2ae31d053e81000 100644
--- a/cabal-install/src/Distribution/Client/Errors.hs
+++ b/cabal-install/src/Distribution/Client/Errors.hs
@@ -184,7 +184,7 @@ data CabalInstallException
   | MissingPackageList Repo.RemoteRepo
   | CmdPathAcceptsNoTargets
   | CmdPathCommandDoesn'tSupportDryRun
-  deriving (Show, Typeable)
+  deriving (Show)
 
 exceptionCodeCabalInstall :: CabalInstallException -> Int
 exceptionCodeCabalInstall e = case e of
diff --git a/cabal-install/src/Distribution/Client/FileMonitor.hs b/cabal-install/src/Distribution/Client/FileMonitor.hs
index fb57aca147460627f194fcca51c969251443ccd9..61607dd199631044d75c2fb46b089d3ba7d90f16 100644
--- a/cabal-install/src/Distribution/Client/FileMonitor.hs
+++ b/cabal-install/src/Distribution/Client/FileMonitor.hs
@@ -1121,7 +1121,7 @@ checkDirectoryModificationTime dir mtime =
 handleErrorCall :: a -> IO a -> IO a
 handleErrorCall e = handle handler
   where
-    handler (ErrorCallWithLocation _ _) = return e
+    handler (ErrorCall _) = return e
 
 -- | Run an IO computation, returning @e@ if there is any 'IOException'.
 --
diff --git a/cabal-install/src/Distribution/Client/HashValue.hs b/cabal-install/src/Distribution/Client/HashValue.hs
index e19956b7ed395e2322f3509f88bb41170a17a9b3..c5698f27f1eedf1fb14e8e2a0f557e162c71437c 100644
--- a/cabal-install/src/Distribution/Client/HashValue.hs
+++ b/cabal-install/src/Distribution/Client/HashValue.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE CPP #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 
 module Distribution.Client.HashValue
@@ -38,7 +37,7 @@ import System.IO (IOMode (..), withBinaryFile)
 -- package ids.
 
 newtype HashValue = HashValue BS.ByteString
-  deriving (Eq, Generic, Show, Typeable)
+  deriving (Eq, Generic, Show)
 
 -- Cannot do any sensible validation here. Although we use SHA256
 -- for stuff we hash ourselves, we can also get hashes from TUF
diff --git a/cabal-install/src/Distribution/Client/IndexUtils.hs b/cabal-install/src/Distribution/Client/IndexUtils.hs
index 705c62d62d11676fcf5edfb7ee03d261db41bf37..d3a6c86a3fe6fd3e7e7504ed12c0b9bdd697ab6f 100644
--- a/cabal-install/src/Distribution/Client/IndexUtils.hs
+++ b/cabal-install/src/Distribution/Client/IndexUtils.hs
@@ -692,7 +692,7 @@ data PreferredVersionsParseError = PreferredVersionsParseError
   , preferredVersionsOriginalDependency :: String
   -- ^ Original input that produced the parser error.
   }
-  deriving (Generic, Read, Show, Eq, Ord, Typeable)
+  deriving (Generic, Read, Show, Eq, Ord)
 
 -- | Parse `preferred-versions` file, collecting parse errors that can be shown
 -- in error messages.
diff --git a/cabal-install/src/Distribution/Client/InstallPlan.hs b/cabal-install/src/Distribution/Client/InstallPlan.hs
index 46212baaccc3a17465d70e8237820f4aac64b420..df719fa59266fdf9c7d65dbc171d34d5c52fa5ed 100644
--- a/cabal-install/src/Distribution/Client/InstallPlan.hs
+++ b/cabal-install/src/Distribution/Client/InstallPlan.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE ConstraintKinds #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE ScopedTypeVariables #-}
@@ -258,7 +257,6 @@ data GenericInstallPlan ipkg srcpkg = GenericInstallPlan
   { planGraph :: !(Graph (GenericPlanPackage ipkg srcpkg))
   , planIndepGoals :: !IndependentGoals
   }
-  deriving (Typeable)
 
 -- | 'GenericInstallPlan' specialised to most commonly used types.
 type InstallPlan =
diff --git a/cabal-install/src/Distribution/Client/ProjectBuilding/Types.hs b/cabal-install/src/Distribution/Client/ProjectBuilding/Types.hs
index 397a01ee68e023090514967c8bc1ec414f5353e5..864455cb540f807113faa4b1138660b025f4f7e9 100644
--- a/cabal-install/src/Distribution/Client/ProjectBuilding/Types.hs
+++ b/cabal-install/src/Distribution/Client/ProjectBuilding/Types.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
-
 -- | Types for the "Distribution.Client.ProjectBuilding"
 --
 -- Moved out to avoid module cycles.
@@ -156,7 +154,7 @@ data BuildFailure = BuildFailure
   { buildFailureLogFile :: Maybe FilePath
   , buildFailureReason :: BuildFailureReason
   }
-  deriving (Show, Typeable)
+  deriving (Show)
 
 instance Exception BuildFailure
 
diff --git a/cabal-install/src/Distribution/Client/ProjectConfig.hs b/cabal-install/src/Distribution/Client/ProjectConfig.hs
index 5f31dc0fab5e998c4c24ceb9b044fe06a5b96aaa..e66ad70d3a9b7f7191addd0a4735995c69e1a498 100644
--- a/cabal-install/src/Distribution/Client/ProjectConfig.hs
+++ b/cabal-install/src/Distribution/Client/ProjectConfig.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE CPP #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE NamedFieldPuns #-}
 {-# LANGUAGE RecordWildCards #-}
@@ -669,7 +668,7 @@ data BadProjectRoot
   | BadProjectRootAbsoluteFileNotFound FilePath
   | BadProjectRootDirFileNotFound FilePath FilePath
   | BadProjectRootFileBroken FilePath
-  deriving (Show, Typeable, Eq)
+  deriving (Show, Eq)
 
 instance Exception BadProjectRoot where
   displayException = renderBadProjectRoot
@@ -904,7 +903,7 @@ data ProjectPackageLocation
 -- | Exception thrown by 'findProjectPackages'.
 data BadPackageLocations
   = BadPackageLocations (Set ProjectConfigProvenance) [BadPackageLocation]
-  deriving (Show, Typeable)
+  deriving (Show)
 
 instance Exception BadPackageLocations where
   displayException = renderBadPackageLocations
@@ -1579,7 +1578,6 @@ data CabalFileParseError
       -- ^ We might discover the spec version the package needs
       [PWarning]
       -- ^ warnings
-  deriving (Typeable)
 
 -- | Manual instance which skips file contents
 instance Show CabalFileParseError where
@@ -1631,7 +1629,7 @@ readSourcePackageCabalFile verbosity pkgfilename content =
 data CabalFileSearchFailure
   = NoCabalFileFound FilePath
   | MultipleCabalFilesFound FilePath
-  deriving (Show, Typeable)
+  deriving (Show)
 
 instance Exception CabalFileSearchFailure
 
@@ -1741,7 +1739,7 @@ truncateString n s
 
 data BadPerPackageCompilerPaths
   = BadPerPackageCompilerPaths [(PackageName, String)]
-  deriving (Show, Typeable)
+  deriving (Show)
 
 instance Exception BadPerPackageCompilerPaths where
   displayException = renderBadPerPackageCompilerPaths
diff --git a/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs b/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs
index a2826390de65c2dedbedaced5de6b2f47bc92d75..1a2b6ae2fa62a27444c77f2767677e3a3cce3f88 100644
--- a/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs
+++ b/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 
@@ -152,7 +151,7 @@ data ProjectConfig = ProjectConfig
   -- any packages which are explicitly named in `cabal.project`.
   , projectConfigSpecificPackage :: MapMappend PackageName PackageConfig
   }
-  deriving (Eq, Show, Generic, Typeable)
+  deriving (Eq, Show, Generic)
 
 -- | That part of the project configuration that only affects /how/ we build
 -- and not the /value/ of the things we build. This means this information
@@ -338,7 +337,7 @@ instance Structured PackageConfig
 -- | Newtype wrapper for 'Map' that provides a 'Monoid' instance that takes
 -- the last value rather than the first value for overlapping keys.
 newtype MapLast k v = MapLast {getMapLast :: Map k v}
-  deriving (Eq, Show, Functor, Generic, Binary, Typeable)
+  deriving (Eq, Show, Functor, Generic, Binary)
 
 instance (Structured k, Structured v) => Structured (MapLast k v)
 
@@ -354,7 +353,7 @@ instance Ord k => Semigroup (MapLast k v) where
 -- | Newtype wrapper for 'Map' that provides a 'Monoid' instance that
 -- 'mappend's values of overlapping keys rather than taking the first.
 newtype MapMappend k v = MapMappend {getMapMappend :: Map k v}
-  deriving (Eq, Show, Functor, Generic, Binary, Typeable)
+  deriving (Eq, Show, Functor, Generic, Binary)
 
 instance (Structured k, Structured v) => Structured (MapMappend k v)
 
@@ -439,7 +438,7 @@ data SolverSettings = SolverSettings
   -- solverSettingOverrideReinstall :: Bool,
   -- solverSettingUpgradeDeps       :: Bool
   }
-  deriving (Eq, Show, Generic, Typeable)
+  deriving (Eq, Show, Generic)
 
 instance Binary SolverSettings
 instance Structured SolverSettings
diff --git a/cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs b/cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs
index 0ac54fce8ce8689c0254fc57c8fc7b89a042da1a..7ee5cb52f41f68ceee05e48e5f1ed7160c591076 100644
--- a/cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs
+++ b/cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE FlexibleInstances #-}
@@ -192,7 +191,7 @@ data ElaboratedSharedConfig = ElaboratedSharedConfig
   -- used.
   , pkgConfigReplOptions :: ReplOptions
   }
-  deriving (Show, Generic, Typeable)
+  deriving (Show, Generic)
 
 -- TODO: [code cleanup] no Eq instance
 
@@ -337,7 +336,7 @@ data ElaboratedConfiguredPackage = ElaboratedConfiguredPackage
     elabPkgOrComp :: ElaboratedPackageOrComponent
   -- ^ Component/package specific information
   }
-  deriving (Eq, Show, Generic, Typeable)
+  deriving (Eq, Show, Generic)
 
 normaliseConfiguredPackage
   :: ElaboratedSharedConfig
@@ -933,7 +932,7 @@ data SetupScriptStyle
   | SetupCustomImplicitDeps
   | SetupNonCustomExternalLib
   | SetupNonCustomInternalLib
-  deriving (Eq, Show, Generic, Typeable)
+  deriving (Eq, Show, Generic)
 
 instance Binary SetupScriptStyle
 instance Structured SetupScriptStyle
diff --git a/cabal-install/src/Distribution/Client/SavedFlags.hs b/cabal-install/src/Distribution/Client/SavedFlags.hs
index 1a598a58fd7d861c5bd7ef4244baa83ae9d6a7b7..1f752e11bd4bf77b8158eb7847e439f3212d5e6a 100644
--- a/cabal-install/src/Distribution/Client/SavedFlags.hs
+++ b/cabal-install/src/Distribution/Client/SavedFlags.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
-
 module Distribution.Client.SavedFlags
   ( readCommandFlags
   , writeCommandFlags
@@ -67,7 +65,6 @@ data SavedArgsError
   = SavedArgsErrorHelp Args
   | SavedArgsErrorList Args
   | SavedArgsErrorOther Args [String]
-  deriving (Typeable)
 
 instance Show SavedArgsError where
   show (SavedArgsErrorHelp args) =
diff --git a/cabal-install/src/Distribution/Client/Security/HTTP.hs b/cabal-install/src/Distribution/Client/Security/HTTP.hs
index 850a437446edad3b3ac6922ceda5738fa12c7438..9e2da46f631f6738def9d3f19999e8e462a2dffd 100644
--- a/cabal-install/src/Distribution/Client/Security/HTTP.hs
+++ b/cabal-install/src/Distribution/Client/Security/HTTP.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE CPP #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ScopedTypeVariables #-}
@@ -179,7 +178,6 @@ mkReqHeaders reqHeaders mRange' =
 -------------------------------------------------------------------------------}
 
 data UnexpectedResponse = UnexpectedResponse URI Int
-  deriving (Typeable)
 
 instance HC.Pretty UnexpectedResponse where
   pretty (UnexpectedResponse uri code) =
diff --git a/cabal-install/src/Distribution/Client/Setup.hs b/cabal-install/src/Distribution/Client/Setup.hs
index ce1436ff9a7321eac31d9c9e0a3e52301e106141..c68f0dec44a229e62db5b200183a7434d934b4b6 100644
--- a/cabal-install/src/Distribution/Client/Setup.hs
+++ b/cabal-install/src/Distribution/Client/Setup.hs
@@ -1675,7 +1675,7 @@ data CheckFlags = CheckFlags
   { checkVerbosity :: Flag Verbosity
   , checkIgnore :: [CheckExplanationIDString]
   }
-  deriving (Show, Typeable)
+  deriving (Show)
 
 defaultCheckFlags :: CheckFlags
 defaultCheckFlags =
diff --git a/cabal-install/src/Distribution/Client/SolverInstallPlan.hs b/cabal-install/src/Distribution/Client/SolverInstallPlan.hs
index f4422080a4b657d47c69bb15938f1855a473b08a..17dcf6d939865aec265266f7d6e533796d783fb8 100644
--- a/cabal-install/src/Distribution/Client/SolverInstallPlan.hs
+++ b/cabal-install/src/Distribution/Client/SolverInstallPlan.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE TypeFamilies #-}
 
@@ -93,7 +92,7 @@ data SolverInstallPlan = SolverInstallPlan
   { planIndex :: !SolverPlanIndex
   , planIndepGoals :: !IndependentGoals
   }
-  deriving (Typeable, Generic)
+  deriving (Generic)
 
 {-
 -- | Much like 'planPkgIdOf', but mapping back to full packages.
diff --git a/cabal-install/src/Distribution/Client/Types/BuildResults.hs b/cabal-install/src/Distribution/Client/Types/BuildResults.hs
index 55c015346201786afbf3b67f4f6890de86fecf83..61ad6e41c96fcd042288d76441e59104ad9ba922 100644
--- a/cabal-install/src/Distribution/Client/Types/BuildResults.hs
+++ b/cabal-install/src/Distribution/Client/Types/BuildResults.hs
@@ -32,7 +32,7 @@ data BuildFailure
   | BuildFailed SomeException
   | TestsFailed SomeException
   | InstallFailed SomeException
-  deriving (Show, Typeable, Generic)
+  deriving (Show, Generic)
 
 instance Exception BuildFailure
 
@@ -48,9 +48,9 @@ data BuildResult
   deriving (Show, Generic)
 
 data DocsResult = DocsNotTried | DocsFailed | DocsOk
-  deriving (Show, Generic, Typeable)
+  deriving (Show, Generic)
 data TestsResult = TestsNotTried | TestsOk
-  deriving (Show, Generic, Typeable)
+  deriving (Show, Generic)
 
 instance Binary BuildFailure
 instance Binary BuildResult
diff --git a/cabal-install/src/Distribution/Client/Types/PackageLocation.hs b/cabal-install/src/Distribution/Client/Types/PackageLocation.hs
index 2f4993e22bd35a914ed570ce6198a80e8a99f389..9a0537aae7aa1b358f78b7402af2b117a4c7bb8d 100644
--- a/cabal-install/src/Distribution/Client/Types/PackageLocation.hs
+++ b/cabal-install/src/Distribution/Client/Types/PackageLocation.hs
@@ -37,7 +37,7 @@ data PackageLocation local
     RepoTarballPackage Repo PackageId local
   | -- | A package available from a version control system source repository
     RemoteSourceRepoPackage SourceRepoMaybe local
-  deriving (Show, Functor, Eq, Ord, Generic, Typeable)
+  deriving (Show, Functor, Eq, Ord, Generic)
 
 instance Binary local => Binary (PackageLocation local)
 instance Structured local => Structured (PackageLocation local)
diff --git a/cabal-install/tests/IntegrationTests2.hs b/cabal-install/tests/IntegrationTests2.hs
index a74d235c6e5e785df1a92ea288eab0bb6c5f75b6..daf6959fbc2ce7cb449d2ce986aad6488df9a441 100644
--- a/cabal-install/tests/IntegrationTests2.hs
+++ b/cabal-install/tests/IntegrationTests2.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE BangPatterns #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ScopedTypeVariables #-}
@@ -2287,7 +2286,6 @@ mkProjectConfig (GhcPath ghcPath) =
     maybeToFlag = maybe mempty toFlag
 
 data GhcPath = GhcPath (Maybe FilePath)
-  deriving (Typeable)
 
 instance IsOption GhcPath where
   defaultValue = GhcPath Nothing
diff --git a/cabal-install/tests/UnitTests/Distribution/Client/JobControl.hs b/cabal-install/tests/UnitTests/Distribution/Client/JobControl.hs
index 73769f91b183c526a21a5275ba5806f380d352ef..068037a1706a49d1e51c81f3aaf0ce9d533d7e20 100644
--- a/cabal-install/tests/UnitTests/Distribution/Client/JobControl.hs
+++ b/cabal-install/tests/UnitTests/Distribution/Client/JobControl.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
-
 module UnitTests.Distribution.Client.JobControl (tests) where
 
 import Distribution.Client.JobControl
@@ -178,7 +176,7 @@ prop_cancel_parallel (Positive (Small maxJobLimit)) xs ys = do
     return $ Set.fromList (xs' ++ ys') `Set.isSubsetOf` Set.fromList (xs ++ ys)
 
 data TestException = TestException Int
-  deriving (Typeable, Show)
+  deriving (Show)
 
 instance Exception TestException
 
diff --git a/cabal-install/tests/UnitTests/Options.hs b/cabal-install/tests/UnitTests/Options.hs
index 232f80a271147cbeab56580a3ca96c788e2e38aa..6971d271a17b8a5b985513bbe6b7a1f0c5e2d7ff 100644
--- a/cabal-install/tests/UnitTests/Options.hs
+++ b/cabal-install/tests/UnitTests/Options.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
-
 module UnitTests.Options
   ( OptionShowSolverLog (..)
   , OptionMtimeChangeDelay (..)
@@ -9,7 +7,6 @@ module UnitTests.Options
 where
 
 import Data.Proxy
-import Data.Typeable
 
 import Test.Tasty.Options
 
@@ -25,7 +22,6 @@ extraOptions =
   ]
 
 newtype OptionShowSolverLog = OptionShowSolverLog Bool
-  deriving (Typeable)
 
 instance IsOption OptionShowSolverLog where
   defaultValue = OptionShowSolverLog False
@@ -35,7 +31,6 @@ instance IsOption OptionShowSolverLog where
   optionCLParser = flagCLParser Nothing (OptionShowSolverLog True)
 
 newtype OptionMtimeChangeDelay = OptionMtimeChangeDelay Int
-  deriving (Typeable)
 
 instance IsOption OptionMtimeChangeDelay where
   defaultValue = OptionMtimeChangeDelay 0
@@ -47,7 +42,6 @@ instance IsOption OptionMtimeChangeDelay where
         ++ "file modification, in microseconds"
 
 newtype RunNetworkTests = RunNetworkTests Bool
-  deriving (Typeable)
 
 instance IsOption RunNetworkTests where
   defaultValue = RunNetworkTests True
diff --git a/cabal-testsuite/src/Test/Cabal/TestCode.hs b/cabal-testsuite/src/Test/Cabal/TestCode.hs
index fc24b21628558b09eb12c3522095fc07a020a82e..ddaa0239465c90fb0b09ad11d9b77b18027e4fed 100644
--- a/cabal-testsuite/src/Test/Cabal/TestCode.hs
+++ b/cabal-testsuite/src/Test/Cabal/TestCode.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE CPP #-}
-{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DerivingStrategies #-}
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 
@@ -17,7 +16,6 @@ module Test.Cabal.TestCode (
 ) where
 
 import Control.Exception (Exception (..))
-import Data.Typeable     (Typeable)
 
 -------------------------------------------------------------------------------
 -- TestCode
@@ -31,7 +29,7 @@ data TestCode
     | TestCodeFail
     | TestCodeFlakyFailed IssueID
     | TestCodeFlakyPassed IssueID
-  deriving (Eq, Show, Read, Typeable)
+  deriving (Eq, Show, Read)
 
 instance Exception TestCode
   where
@@ -53,7 +51,7 @@ isTestCodeSkip _                = False
 type TestPassed = Bool
 
 newtype IssueID = IssueID Int
-  deriving newtype (Eq, Typeable, Num, Show, Read)
+  deriving newtype (Eq, Num, Show, Read)
 
 data FlakyStatus
   = NotFlaky
diff --git a/cabal-validate/src/Cli.hs b/cabal-validate/src/Cli.hs
index 6a3a33c8f40955611ef8e116a1e62609f9342385..7e0e0e8ab7210c215a17ae52c34cbf78eaadd9a7 100644
--- a/cabal-validate/src/Cli.hs
+++ b/cabal-validate/src/Cli.hs
@@ -13,7 +13,6 @@ where
 import Control.Applicative (Alternative (many, (<|>)), (<**>))
 import Control.Exception (Exception (displayException), throw)
 import Control.Monad (forM_, when)
-import Data.Data (Typeable)
 import Data.Maybe (listToMaybe)
 import qualified Data.Text as T
 import qualified Data.Text.Lazy as T (toStrict)
@@ -136,7 +135,7 @@ data VersionParseException = VersionParseException
   , versionExecutable :: FilePath
   -- ^ The compiler which produced the string.
   }
-  deriving (Typeable, Show)
+  deriving (Show)
 
 instance Exception VersionParseException where
   displayException exception =
diff --git a/project-cabal/ghc-latest.config b/project-cabal/ghc-latest.config
index 8b745c024bb0c09cf86363bb5558f3f2e78e8b96..96042ad583bf832dd1b91f6bf9712de260dcf068 100644
--- a/project-cabal/ghc-latest.config
+++ b/project-cabal/ghc-latest.config
@@ -14,11 +14,11 @@ if impl(ghc >= 9.12.0)
     -- Artem, 2024-04-21: I started and then gave up...
         *:base, *:template-haskell, text-short, *:deepseq, *:bytestring, *:ghc-prim
 
-    repository head.hackage.ghc.haskell.org
-        url: https://ghc.gitlab.haskell.org/head.hackage/
-        secure: True
-        key-threshold: 3
-        root-keys:
-            26021a13b401500c8eb2761ca95c61f2d625bfef951b939a8124ed12ecf07329
-            7541f32a4ccca4f97aea3b22f5e593ba2c0267546016b992dfadcd2fe944e55d
-            f76d08be13e9a61a377a85e2fb63f4c5435d40f8feb3e12eb05905edb8cdea89
+--    repository head.hackage.ghc.haskell.org
+--        url: https://ghc.gitlab.haskell.org/head.hackage/
+--        secure: True
+--        key-threshold: 3
+--        root-keys:
+--            26021a13b401500c8eb2761ca95c61f2d625bfef951b939a8124ed12ecf07329
+--            7541f32a4ccca4f97aea3b22f5e593ba2c0267546016b992dfadcd2fe944e55d
+--            f76d08be13e9a61a377a85e2fb63f4c5435d40f8feb3e12eb05905edb8cdea89
diff --git a/templates/SPDX.LicenseExceptionId.template.hs b/templates/SPDX.LicenseExceptionId.template.hs
index aea2fedb586a62d1af05a454e13c10edeacad5ec..0ef6787416b3d487827c925064f4f38a919280ac 100644
--- a/templates/SPDX.LicenseExceptionId.template.hs
+++ b/templates/SPDX.LicenseExceptionId.template.hs
@@ -32,7 +32,7 @@ import qualified Text.PrettyPrint as Disp
 -- | SPDX License Exceptions identifiers list v3.25
 data LicenseExceptionId
 {{ licenseIds }}
-  deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data, Generic)
+  deriving (Eq, Ord, Enum, Bounded, Show, Read, Data, Generic)
 
 instance Binary LicenseExceptionId where
     put = Binary.putWord8 . fromIntegral . fromEnum
diff --git a/templates/SPDX.LicenseId.template.hs b/templates/SPDX.LicenseId.template.hs
index a7de395410f2b8d236f9cb52a568d5a797ef6d99..a7b78903c34839390e542c0b1a0f85e1777e80cf 100644
--- a/templates/SPDX.LicenseId.template.hs
+++ b/templates/SPDX.LicenseId.template.hs
@@ -35,7 +35,7 @@ import qualified Text.PrettyPrint as Disp
 -- | SPDX License identifiers list v3.25
 data LicenseId
 {{ licenseIds }}
-  deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data)
+  deriving (Eq, Ord, Enum, Bounded, Show, Read, Data)
 
 instance Binary LicenseId where
     -- Word16 is encoded in big endianness