
Cheng Shao pushed to branch wip/libffi-3.5.0 at Glasgow Haskell Compiler / GHC Commits: 35826d8b by Matthew Pickering at 2025-06-08T22:00:41+01:00 Hadrian: Add option to generate .hie files for stage1 libraries The +hie_files flavour transformer can be enabled to produce hie files for stage1 libraries. The hie files are produced in the "extra-compilation-artifacts" folder and copied into the resulting bindist. At the moment the hie files are not produced for the release flavour, they add about 170M to the final bindist. Towards #16901 - - - - - e2467dbd by Ryan Hendrickson at 2025-06-09T13:07:05-04:00 Fix various failures to -fprint-unicode-syntax - - - - - 4ebbaf16 by Cheng Shao at 2025-06-11T03:59:52+00:00 libffi: update to 3.5.1 Bumps libffi submodule. - - - - - 23 changed files: - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Parser/PostProcess.hs - hadrian/doc/flavours.md - hadrian/doc/user-settings.md - hadrian/src/Context.hs - hadrian/src/Context/Path.hs - hadrian/src/Flavour.hs - hadrian/src/Flavour/Type.hs - hadrian/src/Settings/Builders/Ghc.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - libffi-tarballs - testsuite/tests/ghci/scripts/T12550.stdout - testsuite/tests/ghci/scripts/T8959b.stderr - testsuite/tests/ghci/scripts/all.T - + testsuite/tests/ghci/scripts/print-unicode-syntax.script - + testsuite/tests/ghci/scripts/print-unicode-syntax.stderr - + testsuite/tests/ghci/scripts/print-unicode-syntax.stdout - testsuite/tests/ghci/should_run/T11825.stdout Changes: ===================================== compiler/GHC/Hs/Binds.hs ===================================== @@ -627,9 +627,9 @@ instance (OutputableBndrId l, OutputableBndrId r) GhcTc -> ppr v ppr_rhs = case dir of - Unidirectional -> ppr_simple (text "<-") + Unidirectional -> ppr_simple larrow ImplicitBidirectional -> ppr_simple equals - ExplicitBidirectional mg -> ppr_simple (text "<-") <+> text "where" $$ + ExplicitBidirectional mg -> ppr_simple larrow <+> text "where" $$ (nest 2 $ pprFunBind mg) pprTicks :: SDoc -> SDoc -> SDoc ===================================== compiler/GHC/Hs/Decls.hs ===================================== @@ -699,7 +699,7 @@ instance OutputableBndrId p TyVarSig _ tv_bndr -> text "=" <+> ppr tv_bndr pp_inj = case mb_inj of Just (L _ (InjectivityAnn _ lhs rhs)) -> - hsep [ vbar, ppr lhs, text "->", hsep (map ppr rhs) ] + hsep [ vbar, ppr lhs, arrow, hsep (map ppr rhs) ] Nothing -> empty (pp_where, pp_eqns) = case info of ClosedTypeFamily mb_eqns -> @@ -868,7 +868,7 @@ instance OutputableBndrId p instance OutputableBndrId p => Outputable (StandaloneKindSig (GhcPass p)) where ppr (StandaloneKindSig _ v ki) - = text "type" <+> pprPrefixOcc (unLoc v) <+> text "::" <+> ppr ki + = text "type" <+> pprPrefixOcc (unLoc v) <+> dcolon <+> ppr ki pp_condecls :: forall p. OutputableBndrId p => [LConDecl (GhcPass p)] -> SDoc pp_condecls cs ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -956,7 +956,7 @@ ppr_expr (HsIf _ e1 e2 e3) ppr_expr (HsMultiIf _ alts) = hang (text "if") 3 (vcat $ toList $ NE.map ppr_alt alts) where ppr_alt (L _ (GRHS _ guards expr)) = - hang vbar 2 (hang (interpp'SP guards) 2 (text "->" <+> pprDeeper (ppr expr))) + hang vbar 2 (hang (interpp'SP guards) 2 (arrow <+> pprDeeper (ppr expr))) ppr_alt (L _ (XGRHS x)) = ppr x -- special case: let ... in let ... @@ -1029,7 +1029,7 @@ ppr_expr (HsUntypedBracket b q) ppr rnq `ppr_with_pending_tc_splices` ps ppr_expr (HsProc _ pat (L _ (HsCmdTop _ cmd))) - = hsep [text "proc", ppr pat, text "->", ppr cmd] + = hsep [text "proc", ppr pat, arrow, ppr cmd] ppr_expr (HsStatic _ e) = hsep [text "static", ppr e] @@ -1844,10 +1844,10 @@ pp_rhs ctxt rhs = matchSeparator ctxt <+> pprDeeper (ppr rhs) matchSeparator :: HsMatchContext fn -> SDoc matchSeparator FunRhs{} = text "=" -matchSeparator CaseAlt = text "->" -matchSeparator LamAlt{} = text "->" -matchSeparator IfAlt = text "->" -matchSeparator ArrowMatchCtxt{} = text "->" +matchSeparator CaseAlt = arrow +matchSeparator LamAlt{} = arrow +matchSeparator IfAlt = arrow +matchSeparator ArrowMatchCtxt{} = arrow matchSeparator PatBindRhs = text "=" matchSeparator PatBindGuards = text "=" matchSeparator StmtCtxt{} = text "<-" ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -1377,7 +1377,7 @@ pprIfaceDecl ss decl@(IfaceFamily { ifName = tycon pp_inj_cond res inj = case filterByList inj binders of [] -> empty - tvs -> hsep [vbar, ppr res, text "->", interppSP (map ifTyConBinderName tvs)] + tvs -> hsep [vbar, ppr res, arrow, interppSP (map ifTyConBinderName tvs)] pp_rhs IfaceDataFamilyTyCon = ppShowIface ss (text "data") @@ -1464,7 +1464,7 @@ pprRoles suppress_if tyCon bndrs roles text "type role" <+> tyCon <+> hsep (map ppr froles) pprStandaloneKindSig :: SDoc -> IfaceType -> SDoc -pprStandaloneKindSig tyCon ty = text "type" <+> tyCon <+> text "::" <+> ppr ty +pprStandaloneKindSig tyCon ty = text "type" <+> tyCon <+> dcolon <+> ppr ty pprInfixIfDeclBndr :: ShowHowMuch -> OccName -> SDoc pprInfixIfDeclBndr (ShowSome _ (AltPpr (Just ppr_bndr))) name ===================================== compiler/GHC/Iface/Type.hs ===================================== @@ -1747,7 +1747,7 @@ pprTyTcApp ctxt_prec tc tys = , IA_Arg (IfaceLitTy (IfaceStrTyLit n)) Required (IA_Arg ty Required IA_Nil) <- tys -> maybeParen ctxt_prec funPrec - $ char '?' <> ftext (getLexicalFastString n) <> text "::" <> ppr_ty topPrec ty + $ char '?' <> ftext (getLexicalFastString n) <> dcolon <> ppr_ty topPrec ty | IfaceTupleTyCon arity sort <- ifaceTyConSort info , not debug ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -1935,7 +1935,7 @@ instance DisambECP (HsCmd GhcPs) where mkHsLitPV (L l a) = cmdFail l (ppr a) mkHsOverLitPV (L l a) = cmdFail (locA l) (ppr a) mkHsWildCardPV l = cmdFail l (text "_") - mkHsTySigPV l a sig _ = cmdFail (locA l) (ppr a <+> text "::" <+> ppr sig) + mkHsTySigPV l a sig _ = cmdFail (locA l) (ppr a <+> dcolon <+> ppr sig) mkHsExplicitListPV l xs _ = cmdFail l $ brackets (pprWithCommas ppr xs) mkHsSplicePV (L l sp) = cmdFail l (pprUntypedSplice True Nothing sp) ===================================== hadrian/doc/flavours.md ===================================== @@ -334,6 +334,8 @@ The supported transformers are listed below: <td>Disable including self-recompilation information in interface files via <code>-fno-write-if-self-recomp</code>. If you are building a distribution you can enable this flag to produce more deterministic interface files.</td> <td><code>hash_unit_ids</code></td> <td>Include a package hash in the unit id of built packages</td> + <td><code>hie_files</code></td> + <td>Produce hie files for stage1 libraries</td> </tr> </table> ===================================== hadrian/doc/user-settings.md ===================================== @@ -47,7 +47,10 @@ data Flavour = Flavour { -> Bool, -- | Whether to build docs and which ones -- (haddocks, user manual, haddock manual) - ghcDocs :: Action DocTargets } + ghcDocs :: Action DocTargets, + -- | Whether to generate .hie files + ghcHieFiles :: Stage -> Bool + } ``` Hadrian provides several built-in flavours (`default`, `quick`, and a few others; see `hadrian/doc/flavours.md`), which can be activated from the command line, @@ -364,6 +367,13 @@ all of the documentation targets: You can pass several `--docs=...` flags, Hadrian will combine their effects. +### HIE files + +The `ghcHieFiles` field controls whether `.hie` files are generated +for source files built with the stage1 compiler. + +For most flavours `.hie` files wil be generated by default. + ### Split sections You can build all or just a few packages with ===================================== hadrian/src/Context.hs ===================================== @@ -3,7 +3,7 @@ module Context ( Context (..), vanillaContext, stageContext, -- * Expressions - getStage, getPackage, getWay, getBuildPath, getPackageDbLoc, getStagedTarget, + getStage, getPackage, getWay, getBuildPath, getHieBuildPath, getPackageDbLoc, getStagedTarget, -- * Paths contextDir, buildPath, buildDir, pkgInplaceConfig, pkgSetupConfigFile, pkgSetupConfigDir, ===================================== hadrian/src/Context/Path.hs ===================================== @@ -42,6 +42,10 @@ buildPath context = buildRoot <&> (-/- buildDir context) getBuildPath :: Expr Context b FilePath getBuildPath = expr . buildPath =<< getContext +-- | The output directory for hie files +getHieBuildPath :: Expr Context b FilePath +getHieBuildPath = (-/- "extra-compilation-artifacts" -/- "hie") <$> getBuildPath + -- | Path to the directory containing haddock timing files, used by -- the haddock perf tests. haddockStatsFilesDir :: Action FilePath ===================================== hadrian/src/Flavour.hs ===================================== @@ -21,6 +21,7 @@ module Flavour , enableHiCore , useNativeBignum , enableTextWithSIMDUTF + , enableHieFiles , omitPragmas , completeSetting @@ -75,6 +76,7 @@ flavourTransformers = M.fromList , "boot_nonmoving_gc" =: enableBootNonmovingGc , "dump_stg" =: enableDumpStg , "hash_unit_ids" =: enableHashUnitIds + , "hie_files" =: enableHieFiles ] where (=:) = (,) @@ -324,6 +326,9 @@ enableTextWithSIMDUTF flavour = flavour { enableHashUnitIds :: Flavour -> Flavour enableHashUnitIds flavour = flavour { hashUnitIds = True } +enableHieFiles :: Flavour -> Flavour +enableHieFiles flavour = flavour { ghcHieFiles = (>= Stage1) } + -- | Build stage2 compiler with -fomit-interface-pragmas to reduce -- recompilation. omitPragmas :: Flavour -> Flavour ===================================== hadrian/src/Flavour/Type.hs ===================================== @@ -51,7 +51,10 @@ data Flavour = Flavour { ghcDocs :: Action DocTargets, -- | Whether to uses hashes or inplace for unit ids - hashUnitIds :: Bool + hashUnitIds :: Bool, + + -- | Whether to generate .hie files + ghcHieFiles :: Stage -> Bool } ===================================== hadrian/src/Settings/Builders/Ghc.hs ===================================== @@ -35,6 +35,9 @@ compileAndLinkHs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do useColor <- shakeColor <$> expr getShakeOptions let hasVanilla = elem vanilla ways hasDynamic = elem dynamic ways + hieFiles <- ghcHieFiles <$> expr flavour + stage <- getStage + hie_path <- getHieBuildPath mconcat [ arg "-Wall" , arg "-Wcompat" , not useColor ? builder (Ghc CompileHs) ? @@ -49,6 +52,10 @@ compileAndLinkHs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do , ghcLinkArgs , defaultGhcWarningsArgs , builder (Ghc CompileHs) ? arg "-c" + , hieFiles stage ? builder (Ghc CompileHs) ? mconcat + [ arg "-fwrite-ide-info" + , arg "-hiedir", arg hie_path + ] , getInputs , arg "-o", arg =<< getOutput ] ===================================== hadrian/src/Settings/Default.hs ===================================== @@ -283,6 +283,7 @@ defaultFlavour = Flavour , ghcDebugAssertions = const False , ghcSplitSections = False , ghcDocs = cmdDocsArgs + , ghcHieFiles = const False , hashUnitIds = False } -- | Default logic for determining whether to build ===================================== hadrian/src/Settings/Flavours/Release.hs ===================================== @@ -11,4 +11,6 @@ releaseFlavour = $ enableHaddock -- 3. Include unit id hashes $ enableHashUnitIds + -- 4. Include hie files (#16901) + -- $ enableHieFiles $ performanceFlavour { name = "release" } ===================================== libffi-tarballs ===================================== @@ -1 +1 @@ -Subproject commit ac7fa3132d382056837cad297ab4c66418febb69 +Subproject commit 1a5955e69b7b139b066cc31507676afc24959dbd ===================================== testsuite/tests/ghci/scripts/T12550.stdout ===================================== @@ -11,13 +11,13 @@ f ∷ ∀ (a ∷ ★ → ★) b. C a ⇒ a b f ∷ ∀ (a ∷ ★ → ★) b. C a ⇒ a b f ∷ ∀ (a ∷ ★ → ★) b. C a ⇒ a b fmap ∷ ∀ (f ∷ ★ → ★) a b. Functor f ⇒ (a → b) → f a → f b -type Functor :: (★ → ★) → Constraint +type Functor ∷ (★ → ★) → Constraint class Functor f where fmap ∷ ∀ a b. (a → b) → f a → f b ... -- Defined in ‘GHC.Internal.Base’ Functor ∷ (★ → ★) → Constraint -type Functor :: (★ → ★) → Constraint +type Functor ∷ (★ → ★) → Constraint class Functor f where fmap ∷ ∀ a b. (a → b) → f a → f b (<$) ∷ ∀ a b. a → f b → f a @@ -77,7 +77,7 @@ datatypeName (a ∷ k1). Datatype d ⇒ t d f a → [Char] -type Datatype :: ∀ {k}. k → Constraint +type Datatype ∷ ∀ {k}. k → Constraint class Datatype d where datatypeName ∷ ∀ k1 (t ∷ k → (k1 → ★) → k1 → ★) (f ∷ k1 → ★) (a ∷ k1). ===================================== testsuite/tests/ghci/scripts/T8959b.stderr ===================================== @@ -1,4 +1,3 @@ - T8959b.hs:5:7: error: [GHC-83865] • Couldn't match expected type ‘Int → Int’ with actual type ‘()’ • In the expression: () @@ -6,11 +5,12 @@ T8959b.hs:5:7: error: [GHC-83865] T8959b.hs:8:7: error: [GHC-83865] • Couldn't match expected type ‘()’ with actual type ‘t0 → m0 t0’ - • In the expression: proc x -> do return ⤙ x - In an equation for ‘bar’: bar = proc x -> do return ⤙ x + • In the expression: proc x → do return ⤙ x + In an equation for ‘bar’: bar = proc x → do return ⤙ x T8959b.hs:10:7: error: [GHC-83865] • Couldn't match expected type ‘(∀ a. a → a) → a1’ with actual type ‘()’ • In the expression: () ∷ (∀ a. a → a) → a In an equation for ‘baz’: baz = () ∷ (∀ a. a → a) → a + ===================================== testsuite/tests/ghci/scripts/all.T ===================================== @@ -357,6 +357,7 @@ test('T20101', normal, ghci_script, ['T20101.script']) test('T20206', normal, ghci_script, ['T20206.script']) test('T20217', normal, ghci_script, ['T20217.script']) test('T20455', normal, ghci_script, ['T20455.script']) +test('print-unicode-syntax', normal, ghci_script, ['print-unicode-syntax.script']) test('shadow-bindings', normal, ghci_script, ['shadow-bindings.script']) test('T925', normal, ghci_script, ['T925.script']) test('T7388', normal, ghci_script, ['T7388.script']) ===================================== testsuite/tests/ghci/scripts/print-unicode-syntax.script ===================================== @@ -0,0 +1,44 @@ +:set -fprint-unicode-syntax +:set -XArrows -XImplicitParams -XMultiWayIf -XPatternSynonyms -XTemplateHaskell -XTypeFamilyDependencies + +--------------------------------------- +-- Double-colon checks + +import Data.Kind +[d| type Foo :: Type |] + +:{ +foo :: (?imp :: Int) => Int +foo = ?imp +:} +:t foo + +proc x -> (_ -< _) :: _ + +--------------------------------------- +-- Rightwards arrow checks + +[d| type family Foo a = b | b -> c |] + +type family Foo a = b | b -> a +:i Foo + +\_ -> [] 0 + +case () of [] -> 0 + +if | [] -> 0 + +:{ +if | True -> 0 + | True -> 1 +:} + +proc _ -> \_ -> undefined -< 0 + +--------------------------------------- +-- Leftwards arrow checks + +[d| pattern Foo x <- Nothing |] + +[d| pattern Foo x <- Nothing where Foo _ = Nothing |] ===================================== testsuite/tests/ghci/scripts/print-unicode-syntax.stderr ===================================== @@ -0,0 +1,56 @@ +<interactive>:8:10: error: [GHC-44432] + • The standalone kind signature for ‘Foo’ + lacks an accompanying binding + • In the Template Haskell quotation: [d| type Foo ∷ Type |] + +<interactive>:16:11: error: [GHC-03790] + Parse error in command: (_ ⤙ _) ∷ _ + +<interactive>:21:5: error: [GHC-76037] + • Not in scope: type variable ‘c’ + • In the Template Haskell quotation: + [d| type family Foo a = b | b → c |] + +<interactive>:26:7: error: [GHC-83865] + • Couldn't match expected type: t0 → t + with actual type: [a0] + • The function ‘[]’ is applied to one visible argument, + but its type ‘[a]’ has none + In the expression: [] 0 + In the expression: \ _ → [] 0 + • Relevant bindings include + it ∷ p → t (bound at <interactive>:26:1) + +<interactive>:28:12: error: [GHC-83865] + • Couldn't match expected type ‘()’ with actual type ‘[a0]’ + • In the pattern: [] + In a case alternative: [] → 0 + In the expression: case () of [] → 0 + +<interactive>:30:6: error: [GHC-83865] + • Couldn't match expected type ‘Bool’ with actual type ‘[a0]’ + • In the expression: [] + In a stmt of a pattern guard for + a multi-way if alternative: + [] + In the expression: if | [] → 0 + +<interactive>:34:6: warning: [GHC-53633] [-Woverlapping-patterns (in -Wdefault)] + Pattern match is redundant + In a multi-way if alternative: | True → ... + +<interactive>:37:11: error: [GHC-83865] + • Couldn't match expected type ‘()’ with actual type ‘(a0, b0)’ + • In the expression: proc _ → \ _ → undefined ⤙ 0 + In an equation for ‘it’: it = proc _ → \ _ → undefined ⤙ 0 + +<interactive>:42:17: error: [GHC-76037] + • Not in scope: ‘x’ + • In the Template Haskell quotation: [d| pattern Foo x ← Nothing |] + +<interactive>:44:17: error: [GHC-76037] + • Not in scope: ‘x’ + • In the Template Haskell quotation: + [d| pattern Foo x ← Nothing where + Foo _ = Nothing |] + ===================================== testsuite/tests/ghci/scripts/print-unicode-syntax.stdout ===================================== @@ -0,0 +1,5 @@ +foo ∷ (?imp∷Int) ⇒ Int +type Foo ∷ ★ → ★ +type family Foo a = b | b → a + -- Defined at <interactive>:23:1 +0 ===================================== testsuite/tests/ghci/should_run/T11825.stdout ===================================== @@ -1,4 +1,4 @@ -type X :: ★ → ★ → Constraint +type X ∷ ★ → ★ → Constraint class X a b | a → b where to ∷ a → b {-# MINIMAL to #-} View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/845df3cf65036503f762bf861fe6dce... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/845df3cf65036503f762bf861fe6dce... You're receiving this email because of your account on gitlab.haskell.org.