Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
-
3c001377
by Cheng Shao at 2025-12-13T05:03:15-05:00
-
123a8d77
by Peter Trommler at 2025-12-13T05:03:57-05:00
-
0b54b5fd
by Andreas Klebinger at 2025-12-13T05:04:38-05:00
-
08b13f7b
by Cheng Shao at 2025-12-13T05:05:18-05:00
-
3b5aecb5
by Ben Gamari at 2025-12-13T23:43:10+01:00
-
3af44b93
by Johan Förberg at 2025-12-13T21:56:37-05:00
20 changed files:
- .gitlab/ci.sh
- .gitlab/test-metrics.sh
- compiler/GHC/Cmm/Opt.hs
- hadrian/src/Hadrian/Haskell/Cabal/Type.hs
- hadrian/src/Hadrian/Haskell/Hash.hs
- hadrian/src/Hadrian/Oracles/ArgsHash.hs
- hadrian/src/Hadrian/Oracles/Cabal/Type.hs
- hadrian/src/Hadrian/Oracles/DirectoryContents.hs
- hadrian/src/Hadrian/Oracles/Path.hs
- hadrian/src/Hadrian/Oracles/TextFile.hs
- hadrian/src/Hadrian/Utilities.hs
- hadrian/src/Oracles/Flavour.hs
- hadrian/src/Oracles/ModuleFiles.hs
- libraries/base/changelog.md
- libraries/exceptions
- libraries/ghc-internal/src/GHC/Internal/Control/Monad/ST/Lazy/Imp.hs
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
Changes:
| ... | ... | @@ -259,6 +259,12 @@ function setup() { |
| 259 | 259 | git config user.email "ghc-ci@gitlab-haskell.org"
|
| 260 | 260 | git config user.name "GHC GitLab CI"
|
| 261 | 261 | |
| 262 | + # Disable auto gc. Useless in a temporary checkout, and
|
|
| 263 | + # non-deterministic "Auto packing the repository in background for
|
|
| 264 | + # optimum performance." message could pop up that confuses the
|
|
| 265 | + # testsuite driver!
|
|
| 266 | + git config gc.auto 0
|
|
| 267 | + |
|
| 262 | 268 | info "====================================================="
|
| 263 | 269 | info "Toolchain versions"
|
| 264 | 270 | info "====================================================="
|
| ... | ... | @@ -17,12 +17,14 @@ fail() { |
| 17 | 17 | |
| 18 | 18 | function pull() {
|
| 19 | 19 | local ref="refs/notes/$REF"
|
| 20 | - # 2023-10-04: `git fetch` started failing, first on Darwin in CI and then on
|
|
| 21 | - # Linux locally, both using git version 2.40.1. See #24055. One workaround is
|
|
| 22 | - # to set a larger http.postBuffer, although this is definitely a workaround.
|
|
| 23 | - # The default should work just fine. The error could be in git, GitLab, or
|
|
| 24 | - # perhaps the networking tube (including all proxies etc) between the two.
|
|
| 25 | - run git -c http.postBuffer=2097152 fetch -f "$NOTES_ORIGIN" "$ref:$ref"
|
|
| 20 | + |
|
| 21 | + # Fetch performance notes from a dedicated promisor remote using a
|
|
| 22 | + # treeless filter, so that individual note blobs are fetched lazily
|
|
| 23 | + # as needed.
|
|
| 24 | + git remote add perf-notes "$NOTES_ORIGIN" || true
|
|
| 25 | + git config fetch.recurseSubmodules false
|
|
| 26 | + git config remote.perf-notes.partialclonefilter tree:0
|
|
| 27 | + run git fetch --force perf-notes "$ref:$ref"
|
|
| 26 | 28 | echo "perf notes ref $ref is $(git rev-parse $ref)"
|
| 27 | 29 | }
|
| 28 | 30 | |
| ... | ... | @@ -81,4 +83,3 @@ case $1 in |
| 81 | 83 | pull) pull ;;
|
| 82 | 84 | *) fail "Invalid mode $1" ;;
|
| 83 | 85 | esac |
| 84 | - |
| ... | ... | @@ -290,9 +290,7 @@ cmmMachOpFoldM _ (MO_Sub _) [CmmLit lit, CmmLit (CmmInt i rep)] |
| 290 | 290 | -- the same comparison at the larger size.
|
| 291 | 291 | |
| 292 | 292 | cmmMachOpFoldM platform cmp [CmmMachOp conv [x], CmmLit (CmmInt i _)]
|
| 293 | - | -- powerPC NCG has a TODO for I8/I16 comparisons, so don't try
|
|
| 294 | - platformArch platform `elem` [ArchX86, ArchX86_64],
|
|
| 295 | - -- if the operand is widened:
|
|
| 293 | + | -- if the operand is widened:
|
|
| 296 | 294 | Just (rep, signed, narrow_fn) <- maybe_conversion conv,
|
| 297 | 295 | -- and this is a comparison operation:
|
| 298 | 296 | Just narrow_cmp <- maybe_comparison cmp rep signed,
|
| ... | ... | @@ -31,7 +31,7 @@ data PackageData = PackageData |
| 31 | 31 | , description :: String
|
| 32 | 32 | , packageDependencies :: [Package]
|
| 33 | 33 | , genericPackageDescription :: GenericPackageDescription
|
| 34 | - } deriving (Eq, Generic, Show, Typeable)
|
|
| 34 | + } deriving (Eq, Generic, Show)
|
|
| 35 | 35 | |
| 36 | 36 | -- | Haskell package metadata obtained after resolving package configuration
|
| 37 | 37 | -- flags and associated conditionals according to the current build context.
|
| ... | ... | @@ -75,7 +75,7 @@ data ContextData = ContextData |
| 75 | 75 | , contextLibdir :: FilePath
|
| 76 | 76 | -- The location where dynamic libraries go
|
| 77 | 77 | , contextDynLibdir :: FilePath
|
| 78 | - } deriving (Eq, Generic, Show, Typeable)
|
|
| 78 | + } deriving (Eq, Generic, Show)
|
|
| 79 | 79 | |
| 80 | 80 | instance Binary PackageData
|
| 81 | 81 | instance Hashable PackageData where hashWithSalt salt = hashWithSalt salt . show
|
| ... | ... | @@ -108,7 +108,7 @@ data PackageHashConfigInputs = PackageHashConfigInputs { |
| 108 | 108 | deriving Show
|
| 109 | 109 | |
| 110 | 110 | newtype PkgHashKey = PkgHashKey (Stage, Package)
|
| 111 | - deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
|
|
| 111 | + deriving (Binary, Eq, Hashable, NFData, Show)
|
|
| 112 | 112 | type instance RuleResult PkgHashKey = String
|
| 113 | 113 | |
| 114 | 114 | pkgHash :: Stage -> Package -> Action String
|
| ... | ... | @@ -38,7 +38,7 @@ trackArgsHash t = do |
| 38 | 38 | void (askOracle $ ArgsHash hashedTarget :: Action Int)
|
| 39 | 39 | |
| 40 | 40 | newtype ArgsHash c b = ArgsHash (Target c b)
|
| 41 | - deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
|
|
| 41 | + deriving (Binary, Eq, Hashable, NFData, Show)
|
|
| 42 | 42 | type instance RuleResult (ArgsHash c b) = Int
|
| 43 | 43 | |
| 44 | 44 | -- | This oracle stores per-target argument list hashes in the Shake database,
|
| ... | ... | @@ -26,13 +26,13 @@ import Stage |
| 26 | 26 | -- | This type of oracle key is used by 'Hadrian.Oracles.Cabal.readPackageData'
|
| 27 | 27 | -- to cache reading and parsing of 'Hadrian.Haskell.Cabal.Type.PackageData'.
|
| 28 | 28 | newtype PackageDataKey = PackageDataKey Package
|
| 29 | - deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
|
|
| 29 | + deriving (Binary, Eq, Hashable, NFData, Show)
|
|
| 30 | 30 | type instance RuleResult PackageDataKey = PackageData
|
| 31 | 31 | |
| 32 | 32 | -- | This type of oracle key is used by 'Hadrian.Oracles.Cabal.readContextData'
|
| 33 | 33 | -- to cache reading and parsing of 'Hadrian.Haskell.Cabal.Type.ContextData'.
|
| 34 | 34 | newtype ContextDataKey = ContextDataKey Context
|
| 35 | - deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
|
|
| 35 | + deriving (Binary, Eq, Hashable, NFData, Show)
|
|
| 36 | 36 | type instance RuleResult ContextDataKey = ContextData
|
| 37 | 37 | |
| 38 | 38 | -- TODO: Should @PackageConfiguration@ be simply @()@? Presumably the pair
|
| ... | ... | @@ -40,7 +40,7 @@ type instance RuleResult ContextDataKey = ContextData |
| 40 | 40 | -- | The result of Cabal package configuration produced by the oracle
|
| 41 | 41 | -- 'Hadrian.Oracles.Cabal.configurePackageGHC'.
|
| 42 | 42 | newtype PackageConfiguration = PackageConfiguration (C.Compiler, C.Platform)
|
| 43 | - deriving (Binary, Eq, Show, Typeable)
|
|
| 43 | + deriving (Binary, Eq, Show)
|
|
| 44 | 44 | |
| 45 | 45 | instance NFData PackageConfiguration where
|
| 46 | 46 | rnf (PackageConfiguration (c, p)) =
|
| ... | ... | @@ -58,5 +58,5 @@ instance Hashable PackageConfiguration where |
| 58 | 58 | -- | This type of oracle key is used by 'Hadrian.Oracles.Cabal.configurePackageGHC'
|
| 59 | 59 | -- to cache configuration of a Cabal package.
|
| 60 | 60 | newtype PackageConfigurationKey = PackageConfigurationKey (Package, Stage)
|
| 61 | - deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
|
|
| 61 | + deriving (Binary, Eq, Hashable, NFData, Show)
|
|
| 62 | 62 | type instance RuleResult PackageConfigurationKey = PackageConfiguration |
| ... | ... | @@ -15,7 +15,7 @@ import Hadrian.Utilities |
| 15 | 15 | import qualified System.Directory.Extra as IO
|
| 16 | 16 | |
| 17 | 17 | data Match = Test FilePattern | Not Match | And [Match] | Or [Match]
|
| 18 | - deriving (Generic, Eq, Show, Typeable)
|
|
| 18 | + deriving (Generic, Eq, Show)
|
|
| 19 | 19 | |
| 20 | 20 | instance Binary Match
|
| 21 | 21 | instance Hashable Match
|
| ... | ... | @@ -54,7 +54,7 @@ copyDirectoryContentsUntracked expr source target = do |
| 54 | 54 | mapM_ cp =<< directoryContents expr source
|
| 55 | 55 | |
| 56 | 56 | newtype DirectoryContents = DirectoryContents (Match, FilePath)
|
| 57 | - deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
|
|
| 57 | + deriving (Binary, Eq, Hashable, NFData, Show)
|
|
| 58 | 58 | type instance RuleResult DirectoryContents = [FilePath]
|
| 59 | 59 | |
| 60 | 60 | -- | This oracle answers 'directoryContents' queries and tracks the results.
|
| ... | ... | @@ -34,11 +34,11 @@ fixAbsolutePathOnWindows path = |
| 34 | 34 | return path
|
| 35 | 35 | |
| 36 | 36 | newtype LookupInPath = LookupInPath String
|
| 37 | - deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
|
|
| 37 | + deriving (Binary, Eq, Hashable, NFData, Show)
|
|
| 38 | 38 | type instance RuleResult LookupInPath = String
|
| 39 | 39 | |
| 40 | 40 | newtype WindowsPath = WindowsPath FilePath
|
| 41 | - deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
|
|
| 41 | + deriving (Binary, Eq, Hashable, NFData, Show)
|
|
| 42 | 42 | type instance RuleResult WindowsPath = String
|
| 43 | 43 | |
| 44 | 44 | -- | Oracles for looking up paths. These are slow and require caching.
|
| ... | ... | @@ -118,15 +118,15 @@ queryTargetTarget :: (Toolchain.Target -> a) -> Action a |
| 118 | 118 | queryTargetTarget f = f <$> getTargetTarget
|
| 119 | 119 | |
| 120 | 120 | newtype KeyValue = KeyValue (FilePath, String)
|
| 121 | - deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
|
|
| 121 | + deriving (Binary, Eq, Hashable, NFData, Show)
|
|
| 122 | 122 | type instance RuleResult KeyValue = Maybe String
|
| 123 | 123 | |
| 124 | 124 | newtype KeyValues = KeyValues (FilePath, String)
|
| 125 | - deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
|
|
| 125 | + deriving (Binary, Eq, Hashable, NFData, Show)
|
|
| 126 | 126 | type instance RuleResult KeyValues = Maybe [String]
|
| 127 | 127 | |
| 128 | 128 | newtype TargetFile = TargetFile FilePath
|
| 129 | - deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
|
|
| 129 | + deriving (Binary, Eq, Hashable, NFData, Show)
|
|
| 130 | 130 | type instance RuleResult TargetFile = Toolchain.Target
|
| 131 | 131 | |
| 132 | 132 | -- | These oracle rules are used to cache and track answers to the following
|
| ... | ... | @@ -298,7 +298,7 @@ userSettingRules defaultValue = do |
| 298 | 298 | extra <- shakeExtra <$> getShakeOptionsRules
|
| 299 | 299 | return $ lookupExtra defaultValue extra
|
| 300 | 300 | |
| 301 | -newtype BuildRoot = BuildRoot FilePath deriving (Typeable, Eq, Show)
|
|
| 301 | +newtype BuildRoot = BuildRoot FilePath deriving (Eq, Show)
|
|
| 302 | 302 | |
| 303 | 303 | -- | All build results are put into the 'buildRoot' directory.
|
| 304 | 304 | buildRoot :: Action FilePath
|
| ... | ... | @@ -484,7 +484,6 @@ putColoured code msg = do |
| 484 | 484 | else putInfo msg
|
| 485 | 485 | |
| 486 | 486 | newtype BuildProgressColour = BuildProgressColour String
|
| 487 | - deriving Typeable
|
|
| 488 | 487 | |
| 489 | 488 | -- | By default, Hadrian tries to figure out if the current terminal
|
| 490 | 489 | -- supports colors using this function. The default can be overridden
|
| ... | ... | @@ -511,7 +510,6 @@ putBuild msg = do |
| 511 | 510 | putColoured code msg
|
| 512 | 511 | |
| 513 | 512 | newtype SuccessColour = SuccessColour String
|
| 514 | - deriving Typeable
|
|
| 515 | 513 | |
| 516 | 514 | -- | Generate an encoded colour for successful output from names
|
| 517 | 515 | mkSuccessColour :: Colour -> SuccessColour
|
| ... | ... | @@ -528,7 +526,6 @@ putSuccess msg = do |
| 528 | 526 | putColoured code msg
|
| 529 | 527 | |
| 530 | 528 | newtype FailureColour = FailureColour String
|
| 531 | - deriving Typeable
|
|
| 532 | 529 | |
| 533 | 530 | -- | Generate an encoded colour for failure output messages
|
| 534 | 531 | mkFailureColour :: Colour -> FailureColour
|
| ... | ... | @@ -544,7 +541,7 @@ putFailure msg = do |
| 544 | 541 | FailureColour code <- userSetting red
|
| 545 | 542 | putColoured code msg
|
| 546 | 543 | |
| 547 | -data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show, Typeable)
|
|
| 544 | +data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show)
|
|
| 548 | 545 | |
| 549 | 546 | -- | Version of 'putBuild' controlled by @--progress-info@ command line argument.
|
| 550 | 547 | putProgressInfo :: String -> Action ()
|
| ... | ... | @@ -14,11 +14,11 @@ import Flavour |
| 14 | 14 | import Settings (flavour)
|
| 15 | 15 | |
| 16 | 16 | newtype DynGhcPrograms =
|
| 17 | - DynGhcPrograms () deriving (Show, Typeable, Eq, Hashable, Binary, NFData)
|
|
| 17 | + DynGhcPrograms () deriving (Show, Eq, Hashable, Binary, NFData)
|
|
| 18 | 18 | type instance RuleResult DynGhcPrograms = Bool
|
| 19 | 19 | |
| 20 | 20 | newtype GhcProfiled =
|
| 21 | - GhcProfiled Stage deriving (Show, Typeable, Eq, Hashable, Binary, NFData)
|
|
| 21 | + GhcProfiled Stage deriving (Show, Eq, Hashable, Binary, NFData)
|
|
| 22 | 22 | type instance RuleResult GhcProfiled = Bool
|
| 23 | 23 | |
| 24 | 24 | oracles :: Rules ()
|
| ... | ... | @@ -16,11 +16,11 @@ import Expression |
| 16 | 16 | type ModuleName = String
|
| 17 | 17 | |
| 18 | 18 | newtype ModuleFiles = ModuleFiles (Stage, Package)
|
| 19 | - deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
|
|
| 19 | + deriving (Binary, Eq, Hashable, NFData, Show)
|
|
| 20 | 20 | type instance RuleResult ModuleFiles = [Maybe FilePath]
|
| 21 | 21 | |
| 22 | 22 | newtype Generator = Generator (Stage, Package, FilePath)
|
| 23 | - deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
|
|
| 23 | + deriving (Binary, Eq, Hashable, NFData, Show)
|
|
| 24 | 24 | type instance RuleResult Generator = Maybe FilePath
|
| 25 | 25 | |
| 26 | 26 | -- | We scan for the following Haskell source extensions when looking for module
|
| ... | ... | @@ -14,6 +14,7 @@ |
| 14 | 14 | * Remove extra laziness from `Data.Bifunctor.Bifunctor` instances for all tuples to have the same laziness as their `Data.Functor.Functor` counterparts (i.e. they became more strict than before) ([CLC proposal #339](https://github.com/haskell/core-libraries-committee/issues/339))
|
| 15 | 15 | * Adjust the strictness of `Data.List.iterate'` to be more reasonable: every element of the output list is forced to WHNF when the `(:)` containing it is forced. ([CLC proposal #335)](https://github.com/haskell/core-libraries-committee/issues/335)
|
| 16 | 16 | * Add `nubOrd` / `nubOrdBy` to `Data.List` and `Data.List.NonEmpty`. ([CLC proposal #336](https://github.com/haskell/core-libraries-committee/issues/336))
|
| 17 | + * Add `Semigroup` and `Monoid` instances for `Control.Monad.ST.Lazy`. ([CLC proposal #374](https://github.com/haskell/core-libraries-committee/issues/374))
|
|
| 17 | 18 | |
| 18 | 19 | ## 4.22.0.0 *TBA*
|
| 19 | 20 | * Shipped with GHC 9.14.1
|
| 1 | -Subproject commit b6c4290124eb1138358bf04ad9f33e67f6c5c1d8 |
|
| 1 | +Subproject commit 81bfd6e0ca631f315658201ae02e30046678f056 |
| ... | ... | @@ -214,6 +214,14 @@ fixST m = ST (\ s -> |
| 214 | 214 | instance MonadFix (ST s) where
|
| 215 | 215 | mfix = fixST
|
| 216 | 216 | |
| 217 | +-- | @since base-4.23.0.0
|
|
| 218 | +instance Semigroup a => Semigroup (ST s a) where
|
|
| 219 | + (<>) = liftA2 (<>)
|
|
| 220 | + |
|
| 221 | +-- | @since base-4.23.0.0
|
|
| 222 | +instance Monoid a => Monoid (ST s a) where
|
|
| 223 | + mempty = pure mempty
|
|
| 224 | + |
|
| 217 | 225 | -- ---------------------------------------------------------------------------
|
| 218 | 226 | -- Strict <--> Lazy
|
| 219 | 227 |
| ... | ... | @@ -11318,6 +11318,7 @@ instance forall a k (b :: k). GHC.Internal.Base.Monoid a => GHC.Internal.Base.Mo |
| 11318 | 11318 | instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11319 | 11319 | instance GHC.Internal.Base.Monoid GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 11320 | 11320 | instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 11321 | +instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
|
| 11321 | 11322 | instance GHC.Internal.Base.Monoid Data.Array.Byte.ByteArray -- Defined in ‘Data.Array.Byte’
|
| 11322 | 11323 | instance forall a. GHC.Internal.Bits.FiniteBits a => GHC.Internal.Base.Monoid (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| 11323 | 11324 | instance forall a. GHC.Internal.Bits.FiniteBits a => GHC.Internal.Base.Monoid (GHC.Internal.Data.Bits.Iff a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| ... | ... | @@ -11372,6 +11373,7 @@ instance forall a k (b :: k). GHC.Internal.Base.Semigroup a => GHC.Internal.Base |
| 11372 | 11373 | instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11373 | 11374 | instance GHC.Internal.Base.Semigroup GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 11374 | 11375 | instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 11376 | +instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
|
| 11375 | 11377 | instance GHC.Internal.Base.Semigroup Data.Array.Byte.ByteArray -- Defined in ‘Data.Array.Byte’
|
| 11376 | 11378 | instance forall a. GHC.Internal.Bits.Bits a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| 11377 | 11379 | instance forall a. GHC.Internal.Bits.FiniteBits a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Bits.Iff a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| ... | ... | @@ -14364,6 +14364,7 @@ instance forall a k (b :: k). GHC.Internal.Base.Monoid a => GHC.Internal.Base.Mo |
| 14364 | 14364 | instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 14365 | 14365 | instance GHC.Internal.Base.Monoid GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 14366 | 14366 | instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 14367 | +instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
|
| 14367 | 14368 | instance GHC.Internal.Base.Monoid Data.Array.Byte.ByteArray -- Defined in ‘Data.Array.Byte’
|
| 14368 | 14369 | instance forall a. GHC.Internal.Bits.FiniteBits a => GHC.Internal.Base.Monoid (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| 14369 | 14370 | instance forall a. GHC.Internal.Bits.FiniteBits a => GHC.Internal.Base.Monoid (GHC.Internal.Data.Bits.Iff a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| ... | ... | @@ -14415,6 +14416,7 @@ instance forall a k (b :: k). GHC.Internal.Base.Semigroup a => GHC.Internal.Base |
| 14415 | 14416 | instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 14416 | 14417 | instance GHC.Internal.Base.Semigroup GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 14417 | 14418 | instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 14419 | +instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
|
| 14418 | 14420 | instance GHC.Internal.Base.Semigroup Data.Array.Byte.ByteArray -- Defined in ‘Data.Array.Byte’
|
| 14419 | 14421 | instance forall a. GHC.Internal.Bits.Bits a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| 14420 | 14422 | instance forall a. GHC.Internal.Bits.FiniteBits a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Bits.Iff a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| ... | ... | @@ -11580,6 +11580,7 @@ instance forall a k (b :: k). GHC.Internal.Base.Monoid a => GHC.Internal.Base.Mo |
| 11580 | 11580 | instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11581 | 11581 | instance GHC.Internal.Base.Monoid GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 11582 | 11582 | instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 11583 | +instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
|
| 11583 | 11584 | instance GHC.Internal.Base.Monoid Data.Array.Byte.ByteArray -- Defined in ‘Data.Array.Byte’
|
| 11584 | 11585 | instance forall a. GHC.Internal.Bits.FiniteBits a => GHC.Internal.Base.Monoid (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| 11585 | 11586 | instance forall a. GHC.Internal.Bits.FiniteBits a => GHC.Internal.Base.Monoid (GHC.Internal.Data.Bits.Iff a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| ... | ... | @@ -11632,6 +11633,7 @@ instance forall a k (b :: k). GHC.Internal.Base.Semigroup a => GHC.Internal.Base |
| 11632 | 11633 | instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11633 | 11634 | instance GHC.Internal.Base.Semigroup GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 11634 | 11635 | instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 11636 | +instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
|
| 11635 | 11637 | instance GHC.Internal.Base.Semigroup Data.Array.Byte.ByteArray -- Defined in ‘Data.Array.Byte’
|
| 11636 | 11638 | instance forall a. GHC.Internal.Bits.Bits a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| 11637 | 11639 | instance forall a. GHC.Internal.Bits.FiniteBits a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Bits.Iff a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| ... | ... | @@ -11318,6 +11318,7 @@ instance forall a k (b :: k). GHC.Internal.Base.Monoid a => GHC.Internal.Base.Mo |
| 11318 | 11318 | instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11319 | 11319 | instance GHC.Internal.Base.Monoid GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 11320 | 11320 | instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 11321 | +instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
|
| 11321 | 11322 | instance GHC.Internal.Base.Monoid Data.Array.Byte.ByteArray -- Defined in ‘Data.Array.Byte’
|
| 11322 | 11323 | instance forall a. GHC.Internal.Bits.FiniteBits a => GHC.Internal.Base.Monoid (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| 11323 | 11324 | instance forall a. GHC.Internal.Bits.FiniteBits a => GHC.Internal.Base.Monoid (GHC.Internal.Data.Bits.Iff a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| ... | ... | @@ -11372,6 +11373,7 @@ instance forall a k (b :: k). GHC.Internal.Base.Semigroup a => GHC.Internal.Base |
| 11372 | 11373 | instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11373 | 11374 | instance GHC.Internal.Base.Semigroup GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 11374 | 11375 | instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 11376 | +instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
|
| 11375 | 11377 | instance GHC.Internal.Base.Semigroup Data.Array.Byte.ByteArray -- Defined in ‘Data.Array.Byte’
|
| 11376 | 11378 | instance forall a. GHC.Internal.Bits.Bits a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
|
| 11377 | 11379 | instance forall a. GHC.Internal.Bits.FiniteBits a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Bits.Iff a) -- Defined in ‘GHC.Internal.Data.Bits’
|