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
-
c4535f96
by Teo Camarasu at 2025-05-13T10:58:45-04:00
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:
| 1 | 1 | {-# LANGUAGE Safe #-}
|
| 2 | 2 | |
| 3 | --- | contains a prettyprinter for the
|
|
| 4 | --- Template Haskell datatypes
|
|
| 5 | -module Language.Haskell.TH.Ppr
|
|
| 6 | - ( module GHC.Internal.TH.Ppr )
|
|
| 7 | - where
|
|
| 3 | +{- | contains a prettyprinter for the
|
|
| 4 | +Template Haskell datatypes
|
|
| 5 | +-}
|
|
| 6 | +module Language.Haskell.TH.Ppr (
|
|
| 7 | + appPrec,
|
|
| 8 | + bar,
|
|
| 9 | + bytesToString,
|
|
| 10 | + commaSep,
|
|
| 11 | + commaSepApplied,
|
|
| 12 | + commaSepWith,
|
|
| 13 | + fromTANormal,
|
|
| 14 | + funPrec,
|
|
| 15 | + hashParens,
|
|
| 16 | + isStarT,
|
|
| 17 | + isSymOcc,
|
|
| 18 | + nestDepth,
|
|
| 19 | + noPrec,
|
|
| 20 | + opPrec,
|
|
| 21 | + parensIf,
|
|
| 22 | + pprBangType,
|
|
| 23 | + pprBndrVis,
|
|
| 24 | + pprBody,
|
|
| 25 | + pprClause,
|
|
| 26 | + pprCtxWith,
|
|
| 27 | + pprCxt,
|
|
| 28 | + pprExp,
|
|
| 29 | + pprFields,
|
|
| 30 | + pprFixity,
|
|
| 31 | + pprForall,
|
|
| 32 | + pprForall',
|
|
| 33 | + pprForallVis,
|
|
| 34 | + pprFunArgType,
|
|
| 35 | + pprGadtRHS,
|
|
| 36 | + pprGuarded,
|
|
| 37 | + pprInfixExp,
|
|
| 38 | + pprInfixT,
|
|
| 39 | + pprLit,
|
|
| 40 | + pprMatchPat,
|
|
| 41 | + pprMaybeExp,
|
|
| 42 | + pprNamespaceSpecifier,
|
|
| 43 | + pprParendType,
|
|
| 44 | + pprParendTypeArg,
|
|
| 45 | + pprPat,
|
|
| 46 | + pprPatSynSig,
|
|
| 47 | + pprPatSynType,
|
|
| 48 | + pprPrefixOcc,
|
|
| 49 | + pprRecFields,
|
|
| 50 | + pprStrictType,
|
|
| 51 | + pprString,
|
|
| 52 | + pprTyApp,
|
|
| 53 | + pprTyLit,
|
|
| 54 | + pprType,
|
|
| 55 | + pprVarBangType,
|
|
| 56 | + pprVarStrictType,
|
|
| 57 | + ppr_bndrs,
|
|
| 58 | + ppr_ctx_preds_with,
|
|
| 59 | + ppr_cxt_preds,
|
|
| 60 | + ppr_data,
|
|
| 61 | + ppr_dec,
|
|
| 62 | + ppr_deriv_clause,
|
|
| 63 | + ppr_deriv_strategy,
|
|
| 64 | + ppr_newtype,
|
|
| 65 | + ppr_overlap,
|
|
| 66 | + ppr_sig,
|
|
| 67 | + ppr_tf_head,
|
|
| 68 | + ppr_tySyn,
|
|
| 69 | + ppr_type_data,
|
|
| 70 | + ppr_typedef,
|
|
| 71 | + pprint,
|
|
| 72 | + qualPrec,
|
|
| 73 | + quoteParens,
|
|
| 74 | + semiSep,
|
|
| 75 | + semiSepWith,
|
|
| 76 | + sepWith,
|
|
| 77 | + showtextl,
|
|
| 78 | + sigPrec,
|
|
| 79 | + split,
|
|
| 80 | + unboxedSumBars,
|
|
| 81 | + unopPrec,
|
|
| 82 | + where_clause,
|
|
| 83 | + ForallVisFlag (..),
|
|
| 84 | + Ppr (..),
|
|
| 85 | + PprFlag (..),
|
|
| 86 | + Precedence,
|
|
| 87 | + TypeArg (..),
|
|
| 88 | +)
|
|
| 89 | +where
|
|
| 8 | 90 | |
| 9 | 91 | import GHC.Internal.TH.Ppr |
| 1 | 1 | {-# LANGUAGE Safe #-}
|
| 2 | 2 | |
| 3 | 3 | -- | Monadic front-end to Text.PrettyPrint
|
| 4 | -module Language.Haskell.TH.PprLib
|
|
| 5 | - ( module GHC.Internal.TH.PprLib )
|
|
| 6 | - where
|
|
| 4 | +module Language.Haskell.TH.PprLib (
|
|
| 5 | + ($$),
|
|
| 6 | + ($+$),
|
|
| 7 | + (<+>),
|
|
| 8 | + (<>),
|
|
| 9 | + arrow,
|
|
| 10 | + braces,
|
|
| 11 | + brackets,
|
|
| 12 | + cat,
|
|
| 13 | + char,
|
|
| 14 | + colon,
|
|
| 15 | + comma,
|
|
| 16 | + dcolon,
|
|
| 17 | + double,
|
|
| 18 | + doubleQuotes,
|
|
| 19 | + empty,
|
|
| 20 | + equals,
|
|
| 21 | + fcat,
|
|
| 22 | + float,
|
|
| 23 | + fsep,
|
|
| 24 | + hang,
|
|
| 25 | + hcat,
|
|
| 26 | + hsep,
|
|
| 27 | + int,
|
|
| 28 | + integer,
|
|
| 29 | + isEmpty,
|
|
| 30 | + lbrace,
|
|
| 31 | + lbrack,
|
|
| 32 | + lparen,
|
|
| 33 | + nest,
|
|
| 34 | + parens,
|
|
| 35 | + pprName,
|
|
| 36 | + pprName',
|
|
| 37 | + ptext,
|
|
| 38 | + punctuate,
|
|
| 39 | + quotes,
|
|
| 40 | + rational,
|
|
| 41 | + rbrace,
|
|
| 42 | + rbrack,
|
|
| 43 | + rparen,
|
|
| 44 | + semi,
|
|
| 45 | + sep,
|
|
| 46 | + space,
|
|
| 47 | + text,
|
|
| 48 | + to_HPJ_Doc,
|
|
| 49 | + vcat,
|
|
| 50 | + Doc,
|
|
| 51 | + PprM,
|
|
| 52 | +)
|
|
| 53 | +where
|
|
| 7 | 54 | |
| 8 | 55 | import GHC.Internal.TH.PprLib
|
| 56 | +import Prelude () |
| ... | ... | @@ -2,13 +2,196 @@ |
| 2 | 2 | {-# LANGUAGE UnboxedTuples #-}
|
| 3 | 3 | {-# LANGUAGE TemplateHaskellQuotes #-}
|
| 4 | 4 | {-# LANGUAGE Trustworthy #-}
|
| 5 | -module Language.Haskell.TH.Syntax
|
|
| 6 | - ( module GHC.Internal.TH.Syntax
|
|
| 7 | - , makeRelativeToProject
|
|
| 8 | - , module GHC.Internal.TH.Lift
|
|
| 9 | - , addrToByteArrayName
|
|
| 10 | - , addrToByteArray
|
|
| 11 | - )
|
|
| 5 | +{-# LANGUAGE UnboxedTuples #-}
|
|
| 6 | + |
|
| 7 | +module Language.Haskell.TH.Syntax (
|
|
| 8 | + Quote (..),
|
|
| 9 | + Exp (..),
|
|
| 10 | + Match (..),
|
|
| 11 | + Clause (..),
|
|
| 12 | + Q (..),
|
|
| 13 | + Pat (..),
|
|
| 14 | + Stmt (..),
|
|
| 15 | + Con (..),
|
|
| 16 | + Type (..),
|
|
| 17 | + Dec (..),
|
|
| 18 | + BangType,
|
|
| 19 | + VarBangType,
|
|
| 20 | + FieldExp,
|
|
| 21 | + FieldPat,
|
|
| 22 | + Name (..),
|
|
| 23 | + FunDep (..),
|
|
| 24 | + Pred,
|
|
| 25 | + RuleBndr (..),
|
|
| 26 | + TySynEqn (..),
|
|
| 27 | + InjectivityAnn (..),
|
|
| 28 | + Kind,
|
|
| 29 | + Overlap (..),
|
|
| 30 | + DerivClause (..),
|
|
| 31 | + DerivStrategy (..),
|
|
| 32 | + Code (..),
|
|
| 33 | + ModName (..),
|
|
| 34 | + addCorePlugin,
|
|
| 35 | + addDependentFile,
|
|
| 36 | + addForeignFile,
|
|
| 37 | + addForeignFilePath,
|
|
| 38 | + addForeignSource,
|
|
| 39 | + addModFinalizer,
|
|
| 40 | + addTempFile,
|
|
| 41 | + addTopDecls,
|
|
| 42 | + badIO,
|
|
| 43 | + bindCode,
|
|
| 44 | + bindCode_,
|
|
| 45 | + cmpEq,
|
|
| 46 | + compareBytes,
|
|
| 47 | + counter,
|
|
| 48 | + defaultFixity,
|
|
| 49 | + eqBytes,
|
|
| 50 | + extsEnabled,
|
|
| 51 | + getDoc,
|
|
| 52 | + getPackageRoot,
|
|
| 53 | + getQ,
|
|
| 54 | + get_cons_names,
|
|
| 55 | + hoistCode,
|
|
| 56 | + isExtEnabled,
|
|
| 57 | + isInstance,
|
|
| 58 | + joinCode,
|
|
| 59 | + liftCode,
|
|
| 60 | + location,
|
|
| 61 | + lookupName,
|
|
| 62 | + lookupTypeName,
|
|
| 63 | + lookupValueName,
|
|
| 64 | + manyName,
|
|
| 65 | + maxPrecedence,
|
|
| 66 | + memcmp,
|
|
| 67 | + mkNameG,
|
|
| 68 | + mkNameU,
|
|
| 69 | + mkOccName,
|
|
| 70 | + mkPkgName,
|
|
| 71 | + mk_tup_name,
|
|
| 72 | + mkName,
|
|
| 73 | + mkNameG_v,
|
|
| 74 | + mkNameG_d,
|
|
| 75 | + mkNameG_tc,
|
|
| 76 | + mkNameL,
|
|
| 77 | + mkNameS,
|
|
| 78 | + unTypeCode,
|
|
| 79 | + mkModName,
|
|
| 80 | + unsafeCodeCoerce,
|
|
| 81 | + mkNameQ,
|
|
| 82 | + mkNameG_fld,
|
|
| 83 | + modString,
|
|
| 84 | + nameBase,
|
|
| 85 | + nameModule,
|
|
| 86 | + namePackage,
|
|
| 87 | + nameSpace,
|
|
| 88 | + newDeclarationGroup,
|
|
| 89 | + newNameIO,
|
|
| 90 | + occString,
|
|
| 91 | + oneName,
|
|
| 92 | + pkgString,
|
|
| 93 | + putDoc,
|
|
| 94 | + putQ,
|
|
| 95 | + recover,
|
|
| 96 | + reify,
|
|
| 97 | + reifyAnnotations,
|
|
| 98 | + reifyConStrictness,
|
|
| 99 | + reifyFixity,
|
|
| 100 | + reifyInstances,
|
|
| 101 | + reifyModule,
|
|
| 102 | + reifyRoles,
|
|
| 103 | + reifyType,
|
|
| 104 | + report,
|
|
| 105 | + reportError,
|
|
| 106 | + reportWarning,
|
|
| 107 | + runIO,
|
|
| 108 | + sequenceQ,
|
|
| 109 | + runQ,
|
|
| 110 | + showName,
|
|
| 111 | + showName',
|
|
| 112 | + thenCmp,
|
|
| 113 | + tupleDataName,
|
|
| 114 | + tupleTypeName,
|
|
| 115 | + unTypeQ,
|
|
| 116 | + unboxedSumDataName,
|
|
| 117 | + unboxedSumTypeName,
|
|
| 118 | + unboxedTupleDataName,
|
|
| 119 | + unboxedTupleTypeName,
|
|
| 120 | + unsafeTExpCoerce,
|
|
| 121 | + ForeignSrcLang (..),
|
|
| 122 | + Extension (..),
|
|
| 123 | + AnnLookup (..),
|
|
| 124 | + AnnTarget (..),
|
|
| 125 | + Arity,
|
|
| 126 | + Bang (..),
|
|
| 127 | + BndrVis (..),
|
|
| 128 | + Body (..),
|
|
| 129 | + Bytes (..),
|
|
| 130 | + Callconv (..),
|
|
| 131 | + CharPos,
|
|
| 132 | + Cxt,
|
|
| 133 | + DecidedStrictness (..),
|
|
| 134 | + DocLoc (..),
|
|
| 135 | + FamilyResultSig (..),
|
|
| 136 | + Fixity (..),
|
|
| 137 | + FixityDirection (..),
|
|
| 138 | + Foreign (..),
|
|
| 139 | + Guard (..),
|
|
| 140 | + Info (..),
|
|
| 141 | + Inline (..),
|
|
| 142 | + InstanceDec,
|
|
| 143 | + Lit (..),
|
|
| 144 | + Loc (..),
|
|
| 145 | + Module (..),
|
|
| 146 | + ModuleInfo (..),
|
|
| 147 | + NameFlavour (..),
|
|
| 148 | + NameIs (..),
|
|
| 149 | + NameSpace (..),
|
|
| 150 | + NamespaceSpecifier (..),
|
|
| 151 | + OccName (..),
|
|
| 152 | + ParentName,
|
|
| 153 | + PatSynArgs (..),
|
|
| 154 | + PatSynDir (..),
|
|
| 155 | + PatSynType,
|
|
| 156 | + Phases (..),
|
|
| 157 | + PkgName (..),
|
|
| 158 | + Pragma (..),
|
|
| 159 | + Quasi (..),
|
|
| 160 | + Range (..),
|
|
| 161 | + Role (..),
|
|
| 162 | + RuleMatch (..),
|
|
| 163 | + Safety (..),
|
|
| 164 | + SourceStrictness (..),
|
|
| 165 | + SourceUnpackedness (..),
|
|
| 166 | + Specificity (..),
|
|
| 167 | + Strict,
|
|
| 168 | + StrictType,
|
|
| 169 | + SumAlt,
|
|
| 170 | + SumArity,
|
|
| 171 | + TExp (..),
|
|
| 172 | + TyLit (..),
|
|
| 173 | + TyVarBndr (..),
|
|
| 174 | + TypeFamilyHead (..),
|
|
| 175 | + Uniq,
|
|
| 176 | + Unlifted,
|
|
| 177 | + VarStrictType,
|
|
| 178 | + makeRelativeToProject,
|
|
| 179 | + liftString,
|
|
| 180 | + Lift (..),
|
|
| 181 | + dataToExpQ,
|
|
| 182 | + dataToPatQ,
|
|
| 183 | + dataToQa,
|
|
| 184 | + falseName,
|
|
| 185 | + justName,
|
|
| 186 | + leftName,
|
|
| 187 | + liftData,
|
|
| 188 | + nonemptyName,
|
|
| 189 | + nothingName,
|
|
| 190 | + rightName,
|
|
| 191 | + trueName,
|
|
| 192 | + addrToByteArrayName,
|
|
| 193 | + addrToByteArray,
|
|
| 194 | +)
|
|
| 12 | 195 | where
|
| 13 | 196 | |
| 14 | 197 | import GHC.Internal.TH.Syntax
|
| ... | ... | @@ -18,7 +201,7 @@ import Data.Array.Byte |
| 18 | 201 | import GHC.Exts
|
| 19 | 202 | import GHC.ST
|
| 20 | 203 | |
| 21 | --- This module completely re-exports 'GHC.Internal.TH.Syntax',
|
|
| 204 | +-- This module completely re-exports 'GHC.Boot.TH.Syntax',
|
|
| 22 | 205 | -- and exports additionally functions that depend on filepath.
|
| 23 | 206 | |
| 24 | 207 | -- | The input is a filepath, which if relative is offset by the package root.
|
| ... | ... | @@ -53,6 +53,10 @@ Library |
| 53 | 53 | |
| 54 | 54 | build-depends:
|
| 55 | 55 | base >= 4.11 && < 4.22,
|
| 56 | + -- We don't directly depend on any of the modules from `ghc-internal`
|
|
| 57 | + -- But we need to depend on it to work around a hadrian bug.
|
|
| 58 | + -- See: https://gitlab.haskell.org/ghc/ghc/-/issues/25705
|
|
| 59 | + ghc-internal == @ProjectVersionForLib@.*,
|
|
| 56 | 60 | ghc-boot-th == @ProjectVersionMunged@
|
| 57 | 61 | |
| 58 | 62 | other-modules:
|