From 7975202ba9010c581918413808ee06fbab9ac85f Mon Sep 17 00:00:00 2001 From: romes Date: Sat, 19 Mar 2022 17:42:46 +0000 Subject: TTG: Rework and improve splices This commit redefines the structure of Splices in the AST. We get rid of `HsSplice` which used to represent typed and untyped splices, quasi quotes, and the result of splicing either an expression, a type or a pattern. Instead we have `HsUntypedSplice` which models an untyped splice or a quasi quoter, which works in practice just like untyped splices. The `HsExpr` constructor `HsSpliceE` which used to be constructed with an `HsSplice` is split into `HsTypedSplice` and `HsUntypedSplice`. The former is directly constructed with an `HsExpr` and the latter now takes an `HsUntypedSplice`. Both `HsType` and `Pat` constructors `HsSpliceTy` and `SplicePat` now take an `HsUntypedSplice` instead of a `HsSplice` (remember only /untyped splices/ can be spliced as types or patterns). The result of splicing an expression, type, or pattern is now comfortably stored in the extension fields `XSpliceTy`, `XSplicePat`, `XUntypedSplice` as, respectively, `HsUntypedSpliceResult (HsType GhcRn)`, `HsUntypedSpliceResult (Pat GhcRn)`, and `HsUntypedSpliceResult (HsExpr GhcRn)` Overall the TTG extension points are now better used to make invalid states unrepresentable and model the progression between stages better. See Note [Lifecycle of an untyped splice, and PendingRnSplice] and Note [Lifecycle of an typed splice, and PendingTcSplice] for more details. Updates haddock submodule Fixes #21263 ------------------------- Metric Decrease: hard_hole_fits ------------------------- --- compiler/Language/Haskell/Syntax/Decls.hs | 19 ++++- compiler/Language/Haskell/Syntax/Expr.hs | 101 +++++--------------------- compiler/Language/Haskell/Syntax/Expr.hs-boot | 4 +- compiler/Language/Haskell/Syntax/Extension.hs | 13 ++-- compiler/Language/Haskell/Syntax/Pat.hs | 4 +- compiler/Language/Haskell/Syntax/Type.hs | 4 +- 6 files changed, 47 insertions(+), 98 deletions(-) (limited to 'compiler/Language/Haskell/Syntax') diff --git a/compiler/Language/Haskell/Syntax/Decls.hs b/compiler/Language/Haskell/Syntax/Decls.hs index 026080d3f6..303105e3d4 100644 --- a/compiler/Language/Haskell/Syntax/Decls.hs +++ b/compiler/Language/Haskell/Syntax/Decls.hs @@ -66,7 +66,7 @@ module Language.Haskell.Syntax.Decls ( -- ** @default@ declarations DefaultDecl(..), LDefaultDecl, -- ** Template haskell declaration splice - SpliceExplicitFlag(..), + SpliceDecoration(..), SpliceDecl(..), LSpliceDecl, -- ** Foreign function interface declarations ForeignDecl(..), LForeignDecl, ForeignImport(..), ForeignExport(..), @@ -95,7 +95,7 @@ module Language.Haskell.Syntax.Decls ( import GHC.Prelude import {-# SOURCE #-} Language.Haskell.Syntax.Expr - ( HsExpr, HsSplice ) + ( HsExpr, HsUntypedSplice ) -- Because Expr imports Decls via HsBracket import Language.Haskell.Syntax.Binds @@ -245,10 +245,21 @@ type LSpliceDecl pass = XRec pass (SpliceDecl pass) data SpliceDecl p = SpliceDecl -- Top level splice (XSpliceDecl p) - (XRec p (HsSplice p)) - SpliceExplicitFlag + (XRec p (HsUntypedSplice p)) + SpliceDecoration -- Whether $( ) variant found, for pretty printing | XSpliceDecl !(XXSpliceDecl p) +-- | A splice can appear with various decorations wrapped around it. This data +-- type captures explicitly how it was originally written, for use in the pretty +-- printer. +data SpliceDecoration + = DollarSplice -- ^ $splice + | BareSplice -- ^ bare splice + deriving (Data, Eq, Show) + +instance Outputable SpliceDecoration where + ppr x = text $ show x + {- ************************************************************************ * * diff --git a/compiler/Language/Haskell/Syntax/Expr.hs b/compiler/Language/Haskell/Syntax/Expr.hs index f964c5d3f6..051edda97f 100644 --- a/compiler/Language/Haskell/Syntax/Expr.hs +++ b/compiler/Language/Haskell/Syntax/Expr.hs @@ -46,13 +46,9 @@ import GHC.Data.FastString -- libraries: import Data.Data hiding (Fixity(..)) -import qualified Data.Data as Data (Fixity(..)) import Data.List.NonEmpty ( NonEmpty ) -import GHCi.RemoteTypes ( ForeignRef ) -import qualified Language.Haskell.TH as TH (Q) - {- Note [RecordDotSyntax field updates] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The extensions @OverloadedRecordDot@ @OverloadedRecordUpdate@ together @@ -603,7 +599,8 @@ data HsExpr p -- 'GHC.Parser.Annotation.AnnClose' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation - | HsSpliceE (XSpliceE p) (HsSplice p) + | HsTypedSplice (XTypedSplice p) (LHsExpr p) -- `$$z` or `$$(f 4)` + | HsUntypedSplice (XUntypedSplice p) (HsUntypedSplice p) ----------------------------------------------------------- -- Arrow notation extension @@ -1542,87 +1539,29 @@ Workshop 2007). Briefly, one writes [p| stuff |] -and the arbitrary string "stuff" gets parsed by the parser 'p', whose -type should be Language.Haskell.TH.Quote.QuasiQuoter. 'p' must be -defined in another module, because we are going to run it here. It's -a bit like a TH splice: - $(p "stuff") - -However, you can do this in patterns as well as terms. Because of this, -the splice is run by the *renamer* rather than the type checker. +and the arbitrary string "stuff" gets parsed by the parser 'p', whose type +should be Language.Haskell.TH.Quote.QuasiQuoter. 'p' must be defined in +another module, because we are going to run it here. It's a bit like an +/untyped/ TH splice where the parser is applied the "stuff" as a string, thus: + $(p "stuff") + +Notice that it's an /untyped/ TH splice: it can occur in patterns and types, as well +as in expressions; and it runs in the renamer. -} -- | Haskell Splice -data HsSplice id - = HsTypedSplice -- $$z or $$(f 4) - (XTypedSplice id) - SpliceDecoration -- Whether $$( ) variant found, for pretty printing - (IdP id) -- A unique name to identify this splice point - (LHsExpr id) -- See Note [Pending Splices] - - | HsUntypedSplice -- $z or $(f 4) - (XUntypedSplice id) - SpliceDecoration -- Whether $( ) variant found, for pretty printing - (IdP id) -- A unique name to identify this splice point - (LHsExpr id) -- See Note [Pending Splices] - - | HsQuasiQuote -- See Note [Quasi-quote overview] - (XQuasiQuote id) - (IdP id) -- Splice point - (IdP id) -- Quoter - SrcSpan -- The span of the enclosed string - FastString -- The enclosed string - - -- AZ:TODO: use XSplice instead of HsSpliced - | HsSpliced -- See Note [Delaying modFinalizers in untyped splices] in - -- GHC.Rename.Splice. - -- This is the result of splicing a splice. It is produced by - -- the renamer and consumed by the typechecker. It lives only - -- between the two. - (XSpliced id) - ThModFinalizers -- TH finalizers produced by the splice. - (HsSplicedThing id) -- The result of splicing - | XSplice !(XXSplice id) -- Extension point; see Note [Trees That Grow] - -- in Language.Haskell.Syntax.Extension - --- | A splice can appear with various decorations wrapped around it. This data --- type captures explicitly how it was originally written, for use in the pretty --- printer. -data SpliceDecoration - = DollarSplice -- ^ $splice or $$splice - | BareSplice -- ^ bare splice - deriving (Data, Eq, Show) - -instance Outputable SpliceDecoration where - ppr x = text $ show x - - -isTypedSplice :: HsSplice id -> Bool -isTypedSplice (HsTypedSplice {}) = True -isTypedSplice _ = False -- Quasi-quotes are untyped splices - --- | Finalizers produced by a splice with --- 'Language.Haskell.TH.Syntax.addModFinalizer' --- --- See Note [Delaying modFinalizers in untyped splices] in GHC.Rename.Splice. For how --- this is used. --- -newtype ThModFinalizers = ThModFinalizers [ForeignRef (TH.Q ())] +data HsUntypedSplice id + = HsUntypedSpliceExpr -- $z or $(f 4) + (XUntypedSpliceExpr id) + (LHsExpr id) --- A Data instance which ignores the argument of 'ThModFinalizers'. -instance Data ThModFinalizers where - gunfold _ z _ = z $ ThModFinalizers [] - toConstr a = mkConstr (dataTypeOf a) "ThModFinalizers" [] Data.Prefix - dataTypeOf a = mkDataType "HsExpr.ThModFinalizers" [toConstr a] - --- | Haskell Spliced Thing --- --- Values that can result from running a splice. -data HsSplicedThing id - = HsSplicedExpr (HsExpr id) -- ^ Haskell Spliced Expression - | HsSplicedTy (HsType id) -- ^ Haskell Spliced Type - | HsSplicedPat (Pat id) -- ^ Haskell Spliced Pattern + | HsQuasiQuote -- See Note [Quasi-quote overview] + (XQuasiQuote id) + (IdP id) -- The quoter (the bit between `[` and `|`) + (XRec id FastString) -- The enclosed string + | XUntypedSplice !(XXUntypedSplice id) -- Extension point; see Note [Trees That Grow] + -- in Language.Haskell.Syntax.Extension -- | Haskell (Untyped) Quote = Expr + Pat + Type + Var data HsQuote p diff --git a/compiler/Language/Haskell/Syntax/Expr.hs-boot b/compiler/Language/Haskell/Syntax/Expr.hs-boot index 3ea7e32708..b6a0d79431 100644 --- a/compiler/Language/Haskell/Syntax/Expr.hs-boot +++ b/compiler/Language/Haskell/Syntax/Expr.hs-boot @@ -12,9 +12,9 @@ import Data.Kind ( Type ) type role HsExpr nominal type role MatchGroup nominal nominal type role GRHSs nominal nominal -type role HsSplice nominal +type role HsUntypedSplice nominal data HsExpr (i :: Type) -data HsSplice (i :: Type) +data HsUntypedSplice (i :: Type) data MatchGroup (a :: Type) (body :: Type) data GRHSs (a :: Type) (body :: Type) type family SyntaxExpr (i :: Type) diff --git a/compiler/Language/Haskell/Syntax/Extension.hs b/compiler/Language/Haskell/Syntax/Extension.hs index dc39d10c99..5cffd96690 100644 --- a/compiler/Language/Haskell/Syntax/Extension.hs +++ b/compiler/Language/Haskell/Syntax/Extension.hs @@ -431,7 +431,8 @@ type family XExprWithTySig x type family XArithSeq x type family XTypedBracket x type family XUntypedBracket x -type family XSpliceE x +type family XTypedSplice x +type family XUntypedSplice x type family XProc x type family XStatic x type family XTick x @@ -463,12 +464,10 @@ type family XMissing x type family XXTupArg x -- ------------------------------------- --- HsSplice type families -type family XTypedSplice x -type family XUntypedSplice x -type family XQuasiQuote x -type family XSpliced x -type family XXSplice x +-- HsUntypedSplice type families +type family XUntypedSpliceExpr x +type family XQuasiQuote x +type family XXUntypedSplice x -- ------------------------------------- -- HsQuoteBracket type families diff --git a/compiler/Language/Haskell/Syntax/Pat.hs b/compiler/Language/Haskell/Syntax/Pat.hs index 2f96d107c0..0e9f11dc1b 100644 --- a/compiler/Language/Haskell/Syntax/Pat.hs +++ b/compiler/Language/Haskell/Syntax/Pat.hs @@ -31,7 +31,7 @@ module Language.Haskell.Syntax.Pat ( import GHC.Prelude -import {-# SOURCE #-} Language.Haskell.Syntax.Expr (SyntaxExpr, LHsExpr, HsSplice) +import {-# SOURCE #-} Language.Haskell.Syntax.Expr (SyntaxExpr, LHsExpr, HsUntypedSplice) -- friends: import Language.Haskell.Syntax.Lit @@ -161,7 +161,7 @@ data Pat p -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | SplicePat (XSplicePat p) - (HsSplice p) -- ^ Splice Pattern (Includes quasi-quotes) + (HsUntypedSplice p) -- ^ Splice Pattern (Includes quasi-quotes) ------------ Literal and n+k patterns --------------- | LitPat (XLitPat p) diff --git a/compiler/Language/Haskell/Syntax/Type.hs b/compiler/Language/Haskell/Syntax/Type.hs index 0c84e9faa6..e394628f25 100644 --- a/compiler/Language/Haskell/Syntax/Type.hs +++ b/compiler/Language/Haskell/Syntax/Type.hs @@ -58,7 +58,7 @@ module Language.Haskell.Syntax.Type ( import GHC.Prelude -import {-# SOURCE #-} Language.Haskell.Syntax.Expr ( HsSplice ) +import {-# SOURCE #-} Language.Haskell.Syntax.Expr ( HsUntypedSplice ) import Language.Haskell.Syntax.Extension @@ -836,7 +836,7 @@ data HsType pass -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | HsSpliceTy (XSpliceTy pass) - (HsSplice pass) -- Includes quasi-quotes + (HsUntypedSplice pass) -- Includes quasi-quotes -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'$('@, -- 'GHC.Parser.Annotation.AnnClose' @')'@ -- cgit v1.2.1