[Git][ghc/ghc][ghc-9.12] 2 commits: template-haskell: fix haddocks

Ben Gamari pushed to branch ghc-9.12 at Glasgow Haskell Compiler / GHC Commits: a2b43e25 by Teo Camarasu at 2025-05-13T10:55:38-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 (cherry picked from commit c3b5b216667d946f096116486b835fe717b2e63a) - - - - - c4535f96 by Teo Camarasu at 2025-05-13T10:58:45-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - 4 changed files: - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in Changes: ===================================== libraries/template-haskell/Language/Haskell/TH/Ppr.hs ===================================== @@ -1,9 +1,91 @@ {-# LANGUAGE Safe #-} --- | contains a prettyprinter for the --- Template Haskell datatypes -module Language.Haskell.TH.Ppr - ( module GHC.Internal.TH.Ppr ) - where +{- | contains a prettyprinter for the +Template Haskell datatypes +-} +module Language.Haskell.TH.Ppr ( + appPrec, + bar, + bytesToString, + commaSep, + commaSepApplied, + commaSepWith, + fromTANormal, + funPrec, + hashParens, + isStarT, + isSymOcc, + nestDepth, + noPrec, + opPrec, + parensIf, + pprBangType, + pprBndrVis, + pprBody, + pprClause, + pprCtxWith, + pprCxt, + pprExp, + pprFields, + pprFixity, + pprForall, + pprForall', + pprForallVis, + pprFunArgType, + pprGadtRHS, + pprGuarded, + pprInfixExp, + pprInfixT, + pprLit, + pprMatchPat, + pprMaybeExp, + pprNamespaceSpecifier, + pprParendType, + pprParendTypeArg, + pprPat, + pprPatSynSig, + pprPatSynType, + pprPrefixOcc, + pprRecFields, + pprStrictType, + pprString, + pprTyApp, + pprTyLit, + pprType, + pprVarBangType, + pprVarStrictType, + ppr_bndrs, + ppr_ctx_preds_with, + ppr_cxt_preds, + ppr_data, + ppr_dec, + ppr_deriv_clause, + ppr_deriv_strategy, + ppr_newtype, + ppr_overlap, + ppr_sig, + ppr_tf_head, + ppr_tySyn, + ppr_type_data, + ppr_typedef, + pprint, + qualPrec, + quoteParens, + semiSep, + semiSepWith, + sepWith, + showtextl, + sigPrec, + split, + unboxedSumBars, + unopPrec, + where_clause, + ForallVisFlag (..), + Ppr (..), + PprFlag (..), + Precedence, + TypeArg (..), +) +where import GHC.Internal.TH.Ppr ===================================== libraries/template-haskell/Language/Haskell/TH/PprLib.hs ===================================== @@ -1,8 +1,56 @@ {-# LANGUAGE Safe #-} -- | Monadic front-end to Text.PrettyPrint -module Language.Haskell.TH.PprLib - ( module GHC.Internal.TH.PprLib ) - where +module Language.Haskell.TH.PprLib ( + ($$), + ($+$), + (<+>), + (<>), + arrow, + braces, + brackets, + cat, + char, + colon, + comma, + dcolon, + double, + doubleQuotes, + empty, + equals, + fcat, + float, + fsep, + hang, + hcat, + hsep, + int, + integer, + isEmpty, + lbrace, + lbrack, + lparen, + nest, + parens, + pprName, + pprName', + ptext, + punctuate, + quotes, + rational, + rbrace, + rbrack, + rparen, + semi, + sep, + space, + text, + to_HPJ_Doc, + vcat, + Doc, + PprM, +) +where import GHC.Internal.TH.PprLib +import Prelude () ===================================== libraries/template-haskell/Language/Haskell/TH/Syntax.hs ===================================== @@ -2,13 +2,196 @@ {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE TemplateHaskellQuotes #-} {-# LANGUAGE Trustworthy #-} -module Language.Haskell.TH.Syntax - ( module GHC.Internal.TH.Syntax - , makeRelativeToProject - , module GHC.Internal.TH.Lift - , addrToByteArrayName - , addrToByteArray - ) +{-# LANGUAGE UnboxedTuples #-} + +module Language.Haskell.TH.Syntax ( + Quote (..), + Exp (..), + Match (..), + Clause (..), + Q (..), + Pat (..), + Stmt (..), + Con (..), + Type (..), + Dec (..), + BangType, + VarBangType, + FieldExp, + FieldPat, + Name (..), + FunDep (..), + Pred, + RuleBndr (..), + TySynEqn (..), + InjectivityAnn (..), + Kind, + Overlap (..), + DerivClause (..), + DerivStrategy (..), + Code (..), + ModName (..), + addCorePlugin, + addDependentFile, + addForeignFile, + addForeignFilePath, + addForeignSource, + addModFinalizer, + addTempFile, + addTopDecls, + badIO, + bindCode, + bindCode_, + cmpEq, + compareBytes, + counter, + defaultFixity, + eqBytes, + extsEnabled, + getDoc, + getPackageRoot, + getQ, + get_cons_names, + hoistCode, + isExtEnabled, + isInstance, + joinCode, + liftCode, + location, + lookupName, + lookupTypeName, + lookupValueName, + manyName, + maxPrecedence, + memcmp, + mkNameG, + mkNameU, + mkOccName, + mkPkgName, + mk_tup_name, + mkName, + mkNameG_v, + mkNameG_d, + mkNameG_tc, + mkNameL, + mkNameS, + unTypeCode, + mkModName, + unsafeCodeCoerce, + mkNameQ, + mkNameG_fld, + modString, + nameBase, + nameModule, + namePackage, + nameSpace, + newDeclarationGroup, + newNameIO, + occString, + oneName, + pkgString, + putDoc, + putQ, + recover, + reify, + reifyAnnotations, + reifyConStrictness, + reifyFixity, + reifyInstances, + reifyModule, + reifyRoles, + reifyType, + report, + reportError, + reportWarning, + runIO, + sequenceQ, + runQ, + showName, + showName', + thenCmp, + tupleDataName, + tupleTypeName, + unTypeQ, + unboxedSumDataName, + unboxedSumTypeName, + unboxedTupleDataName, + unboxedTupleTypeName, + unsafeTExpCoerce, + ForeignSrcLang (..), + Extension (..), + AnnLookup (..), + AnnTarget (..), + Arity, + Bang (..), + BndrVis (..), + Body (..), + Bytes (..), + Callconv (..), + CharPos, + Cxt, + DecidedStrictness (..), + DocLoc (..), + FamilyResultSig (..), + Fixity (..), + FixityDirection (..), + Foreign (..), + Guard (..), + Info (..), + Inline (..), + InstanceDec, + Lit (..), + Loc (..), + Module (..), + ModuleInfo (..), + NameFlavour (..), + NameIs (..), + NameSpace (..), + NamespaceSpecifier (..), + OccName (..), + ParentName, + PatSynArgs (..), + PatSynDir (..), + PatSynType, + Phases (..), + PkgName (..), + Pragma (..), + Quasi (..), + Range (..), + Role (..), + RuleMatch (..), + Safety (..), + SourceStrictness (..), + SourceUnpackedness (..), + Specificity (..), + Strict, + StrictType, + SumAlt, + SumArity, + TExp (..), + TyLit (..), + TyVarBndr (..), + TypeFamilyHead (..), + Uniq, + Unlifted, + VarStrictType, + makeRelativeToProject, + liftString, + Lift (..), + dataToExpQ, + dataToPatQ, + dataToQa, + falseName, + justName, + leftName, + liftData, + nonemptyName, + nothingName, + rightName, + trueName, + addrToByteArrayName, + addrToByteArray, +) where import GHC.Internal.TH.Syntax @@ -18,7 +201,7 @@ import Data.Array.Byte import GHC.Exts import GHC.ST --- This module completely re-exports 'GHC.Internal.TH.Syntax', +-- This module completely re-exports 'GHC.Boot.TH.Syntax', -- and exports additionally functions that depend on filepath. -- | The input is a filepath, which if relative is offset by the package root. ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -53,6 +53,10 @@ Library build-depends: base >= 4.11 && < 4.22, + -- We don't directly depend on any of the modules from `ghc-internal` + -- But we need to depend on it to work around a hadrian bug. + -- See: https://gitlab.haskell.org/ghc/ghc/-/issues/25705 + ghc-internal == @ProjectVersionForLib@.*, ghc-boot-th == @ProjectVersionMunged@ other-modules: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b30f25591e78d42837eff475bbe25fe... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b30f25591e78d42837eff475bbe25fe... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Ben Gamari (@bgamari)