summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorromes <rodrigo.m.mesquita@gmail.com>2022-03-20 16:25:55 +0000
committerromes <rodrigo.m.mesquita@gmail.com>2022-03-20 16:25:55 +0000
commit8546cf8d80f03bd131fe493f4877b0cb5ca5e506 (patch)
treeadd67db5215b8f32a934566cc86f4c4ed929a46d
parent62eeb9cd68f51f9d218972649b9dfb650a8f898d (diff)
downloadhaskell-wip/romes/ttg-splices-improvements-alt.tar.gz
attempt to inline hssplice but we need it elsewhere...wip/romes/ttg-splices-improvements-alt
-rw-r--r--compiler/GHC/Hs/Expr.hs34
-rw-r--r--compiler/Language/Haskell/Syntax/Expr.hs40
-rw-r--r--compiler/Language/Haskell/Syntax/Expr.hs-boot2
-rw-r--r--compiler/Language/Haskell/Syntax/Extension.hs2
-rw-r--r--compiler/Language/Haskell/Syntax/Type.hs2
5 files changed, 31 insertions, 49 deletions
diff --git a/compiler/GHC/Hs/Expr.hs b/compiler/GHC/Hs/Expr.hs
index f8290f9ae9..65af137e41 100644
--- a/compiler/GHC/Hs/Expr.hs
+++ b/compiler/GHC/Hs/Expr.hs
@@ -422,7 +422,6 @@ type instance XArithSeq GhcPs = EpAnn [AddEpAnn]
type instance XArithSeq GhcRn = NoExtField
type instance XArithSeq GhcTc = PostTcExpr
-type instance XSpliceE (GhcPass _) = EpAnnCO
type instance XProc (GhcPass _) = EpAnn [AddEpAnn]
type instance XStatic GhcPs = EpAnn [AddEpAnn]
@@ -492,11 +491,21 @@ tupArgPresent (Missing {}) = False
********************************************************************* -}
type instance XXExpr GhcPs = DataConCantHappen
-type instance XXExpr GhcRn = HsExpansion (HsExpr GhcRn) (HsExpr GhcRn)
+type instance XXExpr GhcRn = XXExprGhcRn
type instance XXExpr GhcTc = XXExprGhcTc
-- HsExpansion: see Note [Rebindable syntax and HsExpansion] below
+data XXExprGhcRn
+ = HsExpansionRn (HsExpansion (HsExpr GhcRn) (HsExpr GhcRn))
+
+ -- 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.
+ | HsSpliceRn
+ ThModFinalizers -- TH finalizers produced by the splice.
+ HsSplicedThing -- The result of splicing
+
data XXExprGhcTc
= WrapExpr -- Type and evidence application and abstractions
{-# UNPACK #-} !(HsWrap HsExpr)
@@ -523,6 +532,8 @@ data XXExprGhcTc
Int -- module-local tick number for False
(LHsExpr GhcTc) -- sub-expression
+ | HsSplicedTc DelayedSplice
+
{- *********************************************************************
* *
@@ -1712,27 +1723,16 @@ data HsSplicedThing
| HsSplicedTy (HsType GhcRn) -- ^ Haskell Spliced Type
| HsSplicedPat (Pat GhcRn) -- ^ Haskell Spliced Pattern
-newtype HsSplicedT = HsSplicedT DelayedSplice deriving (Data)
-
-- (IdP id): A unique name to identify this splice point
-type instance XTypedSplice (GhcPass p) = (EpAnn [AddEpAnn], IdP (GhcPass p))
+type instance XTypedSplice (GhcPass p) = (EpAnnCO, EpAnn [AddEpAnn], IdP (GhcPass p))
-- (IdP id): A unique name to identify this splice point
-type instance XUntypedSplice (GhcPass p) = (EpAnn [AddEpAnn], IdP (GhcPass p))
+type instance XUntypedSplice (GhcPass p) = (EpAnnCO, EpAnn [AddEpAnn], IdP (GhcPass p))
-type instance XQuasiQuote (GhcPass p) = ( (IdP (GhcPass p)) -- Splice point
+type instance XQuasiQuote (GhcPass p) = ( EpAnnCO,
+ , (IdP (GhcPass p)) -- Splice point
, (IdP (GhcPass p)) ) -- Quoter
-type instance XXSplice GhcPs = DataConCantHappen
-
--- 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.
-type instance XXSplice GhcRn = ( ThModFinalizers -- TH finalizers produced by the splice.
- , HsSplicedThing ) -- The result of splicing
-
-type instance XXSplice GhcTc = HsSplicedT
-
-- See Note [Running typed splices in the zonker]
-- These are the arguments that are passed to `GHC.Tc.Gen.Splice.runTopSplice`
data DelayedSplice =
diff --git a/compiler/Language/Haskell/Syntax/Expr.hs b/compiler/Language/Haskell/Syntax/Expr.hs
index 542f648c84..54bba3455e 100644
--- a/compiler/Language/Haskell/Syntax/Expr.hs
+++ b/compiler/Language/Haskell/Syntax/Expr.hs
@@ -596,7 +596,20 @@ 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 -- $$z or $$(f 4)
+ (XTypedSplice p)
+ SpliceDecoration -- Whether $$( ) variant found, for pretty printing
+ (LHsExpr p) -- See Note [Pending Splices]
+
+ | HsUntypedSplice -- $z or $(f 4)
+ (XUntypedSplice p)
+ SpliceDecoration -- Whether $( ) variant found, for pretty printing
+ (LHsExpr p) -- See Note [Pending Splices]
+
+ | HsQuasiQuote -- See Note [Quasi-quote overview]
+ (XQuasiQuote p)
+ SrcSpan -- The span of the enclosed string
+ FastString -- The enclosed string
-----------------------------------------------------------
-- Arrow notation extension
@@ -1541,26 +1554,6 @@ 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.
-}
--- | Haskell Splice
-data HsSplice id
- = HsTypedSplice -- $$z or $$(f 4)
- (XTypedSplice id)
- SpliceDecoration -- Whether $$( ) variant found, for pretty printing
- (LHsExpr id) -- See Note [Pending Splices]
-
- | HsUntypedSplice -- $z or $(f 4)
- (XUntypedSplice id)
- SpliceDecoration -- Whether $( ) variant found, for pretty printing
- (LHsExpr id) -- See Note [Pending Splices]
-
- | HsQuasiQuote -- See Note [Quasi-quote overview]
- (XQuasiQuote id)
- SrcSpan -- The span of the enclosed string
- FastString -- The enclosed string
-
- | 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.
@@ -1573,11 +1566,6 @@ instance Outputable SpliceDecoration where
ppr x = text $ show x
-isTypedSplice :: HsSplice id -> Bool
-isTypedSplice (HsTypedSplice {}) = True
-isTypedSplice _ = False -- Quasi-quotes are untyped splices
-
-
-- | Haskell (Untyped) Quote = Expr + Pat + Type + Var
data HsQuote p
= ExpBr (XExpBr p) (LHsExpr p) -- [| expr |]
diff --git a/compiler/Language/Haskell/Syntax/Expr.hs-boot b/compiler/Language/Haskell/Syntax/Expr.hs-boot
index 3ea7e32708..eded18c6d4 100644
--- a/compiler/Language/Haskell/Syntax/Expr.hs-boot
+++ b/compiler/Language/Haskell/Syntax/Expr.hs-boot
@@ -12,9 +12,7 @@ import Data.Kind ( Type )
type role HsExpr nominal
type role MatchGroup nominal nominal
type role GRHSs nominal nominal
-type role HsSplice nominal
data HsExpr (i :: Type)
-data HsSplice (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 b7239868d4..8c0112f7f3 100644
--- a/compiler/Language/Haskell/Syntax/Extension.hs
+++ b/compiler/Language/Haskell/Syntax/Extension.hs
@@ -431,7 +431,6 @@ type family XExprWithTySig x
type family XArithSeq x
type family XTypedBracket x
type family XUntypedBracket x
-type family XSpliceE x
type family XProc x
type family XStatic x
type family XTick x
@@ -467,7 +466,6 @@ type family XXTupArg x
type family XTypedSplice x
type family XUntypedSplice x
type family XQuasiQuote x
-type family XXSplice x
-- -------------------------------------
-- HsQuoteBracket type families
diff --git a/compiler/Language/Haskell/Syntax/Type.hs b/compiler/Language/Haskell/Syntax/Type.hs
index 10c2c03b48..d2f20c1c20 100644
--- a/compiler/Language/Haskell/Syntax/Type.hs
+++ b/compiler/Language/Haskell/Syntax/Type.hs
@@ -58,8 +58,6 @@ module Language.Haskell.Syntax.Type (
import GHC.Prelude
-import {-# SOURCE #-} Language.Haskell.Syntax.Expr ( HsSplice )
-
import Language.Haskell.Syntax.Extension
import GHC.Types.SourceText