Safe Haskell | None |
---|
Bug25739
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: fa31bae9 by Berk Özkütük at 2025-07-01T18:26:56-04:00 Consider `PromotedDataCon` in `tyConStupidTheta` Haddock checks data declarations for the stupid theta so as not to pretty-print them as empty contexts. Type data declarations end up as `PromotedDataCon`s by the time Haddock performs this check, causing a panic. This commit extends `tyConStupidTheta` so that it returns an empty list for `PromotedDataCon`s. This decision was guided by the fact that type data declarations never have data type contexts (see (R1) in Note [Type data declarations]). Fixes #25739. - - - - - 659cdd02 by Ryan Hendrickson at 2025-07-01T18:27:01-04:00 haddock: Document instances from other packages When attaching instances to `Interface`s, it isn't enough just to look for instances in the list of `Interface`s being processed. We also need to look in the modules on which they depend, including those outside of this package. Fixes #25147. Fixes #26079. - - - - - a4333bb1 by Rodrigo Mesquita at 2025-07-01T18:27:02-04:00 hadrian: Fallback logic for internal interpreter When determining whether to build the internal interpreter, the `make` build system had a fallback case for platforms not in the list of explicitly-supported operating systems and architectures. This fallback says we should try to build the internal interpreter if building dynamic GHC programs (if the architecture is unknown). Fixes #24098 - - - - - b1927b0b by meooow25 at 2025-07-01T18:27:10-04:00 Keep scanl' strict in the head on rewrite `scanl'` forces elements to WHNF when the corresponding `(:)`s are forced. The rewrite rule for `scanl'` missed forcing the first element, which is fixed here with a `seq`. - - - - - 16 changed files: - compiler/GHC/Core/TyCon.hs - hadrian/src/Oracles/Flag.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Settings/Builders/Cabal.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Program.hs - libraries/base/changelog.md - libraries/ghc-internal/src/GHC/Internal/List.hs - utils/haddock/CHANGES.md - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/haddock-test/src/Test/Haddock/Config.hs - utils/haddock/html-test/ref/Bug1004.html - + utils/haddock/html-test/ref/Bug25739.html - + utils/haddock/html-test/src/Bug25739.hs Changes: ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -2709,6 +2709,7 @@ tyConStupidTheta :: TyCon -> [PredType] tyConStupidTheta tc@(TyCon { tyConDetails = details }) | AlgTyCon {algTcStupidTheta = stupid} <- details = stupid | PrimTyCon {} <- details = [] + | PromotedDataCon {} <- details = [] | otherwise = pprPanic "tyConStupidTheta" (ppr tc) -- | Extract the 'TyVar's bound by a vanilla type synonym ===================================== hadrian/src/Oracles/Flag.hs ===================================== @@ -7,7 +7,6 @@ module Oracles.Flag ( targetRTSLinkerOnlySupportsSharedLibs, targetSupportsThreadedRts, targetSupportsSMP, - ghcWithInterpreter, useLibffiForAdjustors, arSupportsDashL, arSupportsAtFile @@ -146,31 +145,5 @@ targetSupportsSMP = do | goodArch -> return True | otherwise -> return False - --- | When cross compiling, enable for stage0 to get ghci --- support. But when not cross compiling, disable for --- stage0, otherwise we introduce extra dependencies --- like haskeline etc, and mixing stageBoot/stage0 libs --- can cause extra trouble (e.g. #25406) --- --- Also checks whether the target supports GHCi. -ghcWithInterpreter :: Stage -> Action Bool -ghcWithInterpreter stage = do - is_cross <- flag CrossCompiling - goodOs <- anyTargetOs [ OSMinGW32, OSLinux, OSSolaris2 -- TODO "cygwin32"?, - , OSFreeBSD, OSDragonFly, OSNetBSD, OSOpenBSD - , OSDarwin, OSKFreeBSD - , OSWasi ] - goodArch <- (||) <$> - anyTargetArch [ ArchX86, ArchX86_64, ArchPPC - , ArchAArch64, ArchS390X - , ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2 - , ArchRISCV64, ArchLoongArch64 - , ArchWasm32 ] - <*> isArmTarget - -- Maybe this should just be false for cross compilers. But for now - -- I've kept the old behaviour where it will say yes. (See #25939) - return $ goodOs && goodArch && (stage >= Stage1 || is_cross) - useLibffiForAdjustors :: Action Bool useLibffiForAdjustors = queryTargetTarget tgtUseLibffiForAdjustors ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -26,6 +26,7 @@ import Utilities import GHC.Toolchain as Toolchain hiding (HsCpp(HsCpp)) import GHC.Toolchain.Program import GHC.Platform.ArchOS +import Settings.Program (ghcWithInterpreter) -- | Track this file to rebuild generated files whenever it changes. trackGenerateHs :: Expr () ===================================== hadrian/src/Settings/Builders/Cabal.hs ===================================== @@ -11,7 +11,7 @@ import Settings.Builders.Common import qualified Settings.Builders.Common as S import Control.Exception (assert) import qualified Data.Set as Set -import Settings.Program (programContext) +import Settings.Program (programContext, ghcWithInterpreter) import GHC.Toolchain (ccLinkProgram, tgtCCompilerLink) import GHC.Toolchain.Program (prgFlags) ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -11,6 +11,7 @@ import Settings.Builders.Common (wayCcArgs) import GHC.Toolchain.Target import GHC.Platform.ArchOS import Data.Version.Extra +import Settings.Program (ghcWithInterpreter) -- | Package-specific command-line arguments. packageArgs :: Args ===================================== hadrian/src/Settings/Program.hs ===================================== @@ -1,12 +1,17 @@ module Settings.Program ( programContext + , ghcWithInterpreter ) where import Base import Context import Oracles.Flavour +import Oracles.Flag import Packages +import GHC.Platform.ArchOS +import Settings.Builders.Common (anyTargetOs, anyTargetArch, isArmTarget) + -- TODO: there is duplication and inconsistency between this and -- Rules.Program.getProgramContexts. There should only be one way to -- get a context/contexts for a given stage and package. @@ -24,3 +29,33 @@ programContext stage pkg = do notStage0 (Stage0 {}) = False notStage0 _ = True + +-- | When cross compiling, enable for stage0 to get ghci +-- support. But when not cross compiling, disable for +-- stage0, otherwise we introduce extra dependencies +-- like haskeline etc, and mixing stageBoot/stage0 libs +-- can cause extra trouble (e.g. #25406) +-- +-- Also checks whether the target supports GHCi. +ghcWithInterpreter :: Stage -> Action Bool +ghcWithInterpreter stage = do + is_cross <- flag CrossCompiling + goodOs <- anyTargetOs [ OSMinGW32, OSLinux, OSSolaris2 -- TODO "cygwin32"?, + , OSFreeBSD, OSDragonFly, OSNetBSD, OSOpenBSD + , OSDarwin, OSKFreeBSD + , OSWasi ] + goodArch <- (||) <$> + anyTargetArch [ ArchX86, ArchX86_64, ArchPPC + , ArchAArch64, ArchS390X + , ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2 + , ArchRISCV64, ArchLoongArch64 + , ArchWasm32 ] + <*> isArmTarget + -- The explicit support list is essentially a list of platforms for which + -- the RTS linker has support. If the RTS linker is not supported then we + -- fall back on dynamic linking: + dynamicGhcProgs <- askDynGhcPrograms + + -- Maybe this should just be false for cross compilers. But for now + -- I've kept the old behaviour where it will say yes. (See #25939) + return $ ((goodOs && goodArch) || dynamicGhcProgs) && (stage >= Stage1 || is_cross) ===================================== libraries/base/changelog.md ===================================== @@ -26,6 +26,7 @@ * Expose constructor and field of `Backtraces` from `Control.Exception.Backtrace`, as per [CLC #199](https://github.com/haskell/core-libraries-committee/issues/199#issuecomment-...) * Fix incorrect results of `integerPowMod` when the base is 0 and the exponent is negative, and `integerRecipMod` when the modulus is zero ([#26017](https://gitlab.haskell.org/ghc/ghc/-/issues/26017)). + * Fix the rewrite rule for `scanl'` not being strict in the first element of the output list ([#26143](https://gitlab.haskell.org/ghc/ghc/-/issues/26143)). ## 4.21.0.0 *December 2024* ===================================== libraries/ghc-internal/src/GHC/Internal/List.hs ===================================== @@ -601,7 +601,7 @@ scanl' = scanlGo' -- See Note [scanl rewrite rules] {-# RULES "scanl'" [~1] forall f a bs . scanl' f a bs = - build (\c n -> a `c` foldr (scanlFB' f c) (flipSeq n) bs a) + build (\c n -> a `seq` (a `c` foldr (scanlFB' f c) (flipSeq n) bs a)) "scanlList'" [1] forall f a bs . foldr (scanlFB' f (:)) (flipSeq []) bs a = tail (scanl' f a bs) #-} ===================================== utils/haddock/CHANGES.md ===================================== @@ -1,6 +1,8 @@ ## Changes in 2.32.0 * Add highlighting for inline-code-blocks (sections enclosed in @'s) + * Fix missing documentation for orphan instances from other packages. + * Add incremental mode to support rendering documentation one module at a time. * The flag `--no-compilation` has been added. This flag causes Haddock to avoid ===================================== utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs ===================================== @@ -88,7 +88,10 @@ attachInstances expInfo ifaces instIfaceMap isOneShot = do , fromOrig == Just True || not (null reExp) ] mods_to_load = moduleSetElts mods - mods_visible = mkModuleSet $ map ifaceMod ifaces + -- We need to ensure orphans in modules outside of this package are included. + -- See https://gitlab.haskell.org/ghc/ghc/-/issues/25147 + -- and https://gitlab.haskell.org/ghc/ghc/-/issues/26079 + mods_visible = mkModuleSet $ concatMap (liftA2 (:) ifaceMod ifaceOrphanDeps) ifaces (_msgs, mb_index) <- do hsc_env <- getSession ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -59,6 +59,7 @@ import GHC.Types.Name.Set import GHC.Types.SafeHaskell import qualified GHC.Types.SrcLoc as SrcLoc import qualified GHC.Types.Unique.Map as UniqMap +import GHC.Unit.Module.Deps (dep_orphs) import GHC.Unit.Module.ModIface import GHC.Unit.State (PackageName (..), UnitState) import GHC.Utils.Outputable (SDocContext) @@ -270,6 +271,7 @@ createInterface1' flags unit_state dflags hie_file mod_iface ifaces inst_ifaces , ifaceVisibleExports = visible_names , ifaceFixMap = fixities , ifaceInstances = instances + , ifaceOrphanDeps = dep_orphs $ mi_deps mod_iface , ifaceOrphanInstances = [] -- Filled in attachInstances , ifaceRnOrphanInstances = [] -- Filled in renameInterfaceRn , ifaceHaddockCoverage = coverage ===================================== utils/haddock/haddock-api/src/Haddock/Types.hs ===================================== @@ -134,6 +134,9 @@ data Interface = Interface -- Names from modules that are entirely re-exported don't count as visible. , ifaceInstances :: [ClsInst] -- ^ Instances exported by the module. + , ifaceOrphanDeps :: [Module] + -- ^ The list of modules to check for orphan instances if this module is + -- imported. , ifaceOrphanInstances :: [DocInstance GhcRn] -- ^ Orphan instances , ifaceRnOrphanInstances :: [DocInstance DocNameI] ===================================== utils/haddock/haddock-test/src/Test/Haddock/Config.hs ===================================== @@ -262,6 +262,7 @@ baseDependencies ghcPath = do pkgs = [ "array" , "base" + , "deepseq" , "ghc-prim" , "process" , "template-haskell" ===================================== utils/haddock/html-test/ref/Bug1004.html ===================================== @@ -833,7 +833,61 @@ ><tr ><td class="src clearfix" > (NFData1 f, NFData1 g) => NFData1 (Product f g) #
Since: deepseq-1.4.3.0
Defined in Control.DeepSeq
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Applicative:10" ></span > <span class="breakable" >(</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Functor:11" ></span > <span class="breakable" >(</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monad:12" ></span > <span class="breakable" >(</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadPlus:13" ></span > <span class="breakable" >(</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadFix:14" ></span > <span class="breakable" >(</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadZip:15" ></span > <span class="breakable" >(</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Foldable:16" ></span > <span class="breakable" >(</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Traversable:17" ></span > <span class="breakable" >(</tr ><tr >
Note: in deepseq-1.5.0.0
this instance's superclasses were changed.
Since: deepseq-1.4.3.0
Defined in Control.DeepSeq
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Semigroup:20" ></span > <span class="breakable" >(</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Eq:21" ></span > <span class="breakable" >(</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Ord:22" ></span > <span class="breakable" >(</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Data:23" ></span > <span class="breakable" >(</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Generic:24" ></span > <a href="#" title="GHC.Generics" >Generic</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Read:25" ></span > <span class="breakable" >(</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Show:26" ></span > <span class="breakable" >(</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep1:27" ></span > <span class="keyword" >type</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep:28" ></span > <span class="keyword" >type</tr ><tr >