Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 3c2f4bb4 by sheaf at 2025-11-11T11:47:28-05:00 Preserve user-written kinds in data declarations This commit ensures that we preserve the user-written kind for data declarations, e.g. in type T2T = Type -> Type type D :: T2T data D a where { .. } that we preserve the user-written kind of D as 'T2T', instead of expanding the type synonym 'T2T' during kind checking. We do this by storing 'tyConKind' separately from 'tyConResKind'. This means that 'tyConKind' is not necessarily equal to 'mkTyConKind binders res_kind', as e.g. in the above example the former is 'T2T' while the latter is 'Type -> Type'. This is explained in Note [Preserve user-written TyCon kind] in GHC.Core.TyCon. This is particularly important for Haddock, as the kinds stored in interface files affect the generated documentation, and we want to preserve the user-written types as much as possible. - - - - - 19859584 by sheaf at 2025-11-11T11:47:28-05:00 Store user-written datacon tvs in interface files This commit ensures we store the user-written quantified type variables of data constructors in interface files, e.g. in data D a where MkD1 :: forall x. x -> D x MkD2 :: forall u v. u -> v -> D v The previous behaviour was to rename the universal variables to match the universal variables of the data constructor. This was undesirable because the names that end up in interface files end up mattering for generated Haddock documentation; it's better to preserve the user-written type variables. Moreover, the universal variables may not have been user-written at all, e.g. in an example such as: type T2T = Type -> Type data G :: T2T where MkG :: forall x. D x Here GHC will invent the type variable name 'a' for the first binder of the TyCon G. We really don't want to then rename the user-written 'x' into the generated 'a'. - - - - - 034b2056 by sheaf at 2025-11-11T11:47:28-05:00 DataCon univ_tvs names: pick TyCon over inferred This commit changes how we compute the names of universal type variables in GADT data constructors. This augments the existing logic that chose which type variable name to use, in GHC.Tc.TyCl.mkGADTVars. We continue to prefer DataCon tv names for user-written binders, but we now prefer TyCon tv names for inferred (non-user-written) DataCon binders. This makes a difference in examples such as: type (:~~:) :: k1 -> k2 -> Type data a :~~: b where HRefl :: a :~~: a Before this patch, we ended up giving HRefl the type: forall {k2}. forall (a :: k2). a :~~: a whereas we now give it the type: forall {k1}. forall (a :: k1). a :~~: a The important part isn't really 'k1' or 'k2', but more that the inferred type variable names of the DataCon can be arbitrary/unpredictable (as they are chosen by GHC and depend on how unification proceeds), so it's much better to use the more predictable TyCon type variable names. - - - - - 95078d00 by sheaf at 2025-11-11T11:47:28-05:00 Backpack Rename: use explicit record construction This commit updates the Backpack boilerplate in GHC.Iface.Rename to use explicit record construction rather than record update. This makes sure that the code stays up to date when the underlying constructors change (e.g. new fields are added). The rationale is further explained in Note [Prefer explicit record construction]. - - - - - 2bf36263 by sheaf at 2025-11-11T11:47:28-05:00 Store # eta binders in TyCon and use for Haddock This commit stores the number of TyCon binders that were introduced by eta-expansion (by the function GHC.Tc.Gen.HsType.splitTyConKind). This is then used to pretty-print the TyCon as the user wrote it, e.g. for type Effect :: (Type -> Type) -> Type -> Type data State s :: Effect where {..} -- arity 3 GHC will eta-expand the data declaration to data State s a b where {..} but also store in the 'TyCon' that the number of binders introduced by this eta expansion is 2. This allows us, in 'Haddock.Convert.synifyTyConKindSig', to recover the original user-written syntax, preserving the user's intent in Haddock documentation. See Note [Inline kind signatures with GADTSyntax] in Haddock.Convert. - - - - - 49 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/TyCl/Instance.hs - testsuite/tests/backpack/should_fail/T19244a.stderr - testsuite/tests/dependent/should_fail/T11334b.stderr - testsuite/tests/generics/T10604/T10604_deriving.stderr - testsuite/tests/ghci.debugger/scripts/print012.stdout - testsuite/tests/ghci/scripts/T10321.stdout - testsuite/tests/ghci/scripts/T24459.stdout - testsuite/tests/ghci/scripts/T7730.stdout - testsuite/tests/ghci/scripts/ghci065.stdout - 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 - testsuite/tests/rename/should_fail/rnfail055.stderr - testsuite/tests/saks/should_compile/saks023.stdout - testsuite/tests/saks/should_compile/saks034.stdout - testsuite/tests/saks/should_compile/saks035.stdout - testsuite/tests/showIface/Makefile - + testsuite/tests/showIface/T26246a.hs - + testsuite/tests/showIface/T26246a.stdout - testsuite/tests/showIface/all.T - testsuite/tests/typecheck/T16127/T16127.stderr - testsuite/tests/typecheck/should_compile/T22560d.stdout - testsuite/tests/typecheck/should_fail/T15629.stderr - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/html-test/ref/Bug1004.html - utils/haddock/html-test/ref/Bug1050.html - + utils/haddock/html-test/ref/Bug26246.html - utils/haddock/html-test/ref/Bug85.html - utils/haddock/html-test/ref/Bug923.html - utils/haddock/html-test/ref/BundledPatterns.html - utils/haddock/html-test/ref/BundledPatterns2.html - utils/haddock/html-test/ref/ConstructorPatternExport.html - utils/haddock/html-test/ref/GADTRecords.html - utils/haddock/html-test/ref/LinearTypes.html - utils/haddock/html-test/ref/PromotedTypes.html - + utils/haddock/html-test/src/Bug26246.hs - utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac7b737e8da74b2508994867ede0bec... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac7b737e8da74b2508994867ede0bec... You're receiving this email because of your account on gitlab.haskell.org.