Skip to content

Commit

Permalink
CI: add GHC 9.12 (haskell#10667)
Browse files Browse the repository at this point in the history
* GHC 9.12 compat: deriving Typeable has to go

9.12 turned it into a warning

* GHC 9.12 compat: ErrorCallWithLocation got deprecated

* CI: add 9.12
  • Loading branch information
ulysses4ever authored Dec 26, 2024
1 parent 731f699 commit 3792794
Show file tree
Hide file tree
Showing 132 changed files with 173 additions and 259 deletions.
3 changes: 2 additions & 1 deletion .github/workflows/validate.yml
Original file line number Diff line number Diff line change
Expand Up @@ -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",
Expand Down
4 changes: 2 additions & 2 deletions Cabal-syntax/src/Distribution/Backpack.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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?

Expand Down Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/CabalSpecVersion.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 0 additions & 2 deletions Cabal-syntax/src/Distribution/Compat/Graph.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
Expand Down Expand Up @@ -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
Expand Down
3 changes: 1 addition & 2 deletions Cabal-syntax/src/Distribution/Compat/NonEmptySet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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
Expand Down
6 changes: 2 additions & 4 deletions Cabal-syntax/src/Distribution/Compat/Semigroup.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
Expand All @@ -18,7 +17,6 @@ module Distribution.Compat.Semigroup
, gmempty
) where

import Data.Typeable (Typeable)
import Distribution.Compat.Binary (Binary)
import Distribution.Utils.Structured (Structured)

Expand All @@ -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)

Expand All @@ -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)

Expand Down
7 changes: 3 additions & 4 deletions Cabal-syntax/src/Distribution/Compiler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -141,7 +141,6 @@ data PerCompilerFlavor v = PerCompilerFlavor v v
, Read
, Eq
, Ord
, Typeable
, Data
, Functor
, Foldable
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/License.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/ModuleName.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/SPDX/License.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/SPDX/LicenseExceptionId.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
4 changes: 2 additions & 2 deletions Cabal-syntax/src/Distribution/SPDX/LicenseExpression.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/SPDX/LicenseId.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/SPDX/LicenseReference.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
6 changes: 3 additions & 3 deletions Cabal-syntax/src/Distribution/System.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down
3 changes: 1 addition & 2 deletions Cabal-syntax/src/Distribution/Types/AbiDependency.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}

module Distribution.Types.AbiDependency where
Expand Down Expand Up @@ -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) =
Expand Down
3 changes: 1 addition & 2 deletions Cabal-syntax/src/Distribution/Types/AbiHash.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}

module Distribution.Types.AbiHash
Expand Down Expand Up @@ -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'
--
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/Types/Benchmark.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/Types/BenchmarkInterface.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/Types/BenchmarkType.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/Types/BuildInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/Types/BuildType.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/Types/ComponentId.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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'
--
Expand Down
5 changes: 2 additions & 3 deletions Cabal-syntax/src/Distribution/Types/ComponentName.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PatternSynonyms #-}

Expand All @@ -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)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}

module Distribution.Types.ComponentRequestedSpec
Expand Down Expand Up @@ -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
Expand Down
4 changes: 2 additions & 2 deletions Cabal-syntax/src/Distribution/Types/CondTree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand All @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/Types/Condition.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/Types/ConfVar.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion Cabal-syntax/src/Distribution/Types/Dependency.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
Loading

0 comments on commit 3792794

Please sign in to comment.