[commit: ghc] context-quantification-4426: Split SpliceExplicitFlag off HsExplicitFlag (c143a93)
git at git.haskell.org
git at git.haskell.org
Sun Sep 14 14:25:47 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : context-quantification-4426
Link : http://ghc.haskell.org/trac/ghc/changeset/c143a93b00cc350f67db612f2c45047390ba77e6/ghc
>---------------------------------------------------------------
commit c143a93b00cc350f67db612f2c45047390ba77e6
Author: Krzysztof Gogolewski <krz.gogolewski at gmail.com>
Date: Sun Sep 14 13:17:27 2014 +0200
Split SpliceExplicitFlag off HsExplicitFlag
SpliceExplicitFlag is used for TH splice explicitness, while
HsExplicitFlag for type variable quantification.
>---------------------------------------------------------------
c143a93b00cc350f67db612f2c45047390ba77e6
compiler/hsSyn/HsDecls.lhs | 8 ++++++--
compiler/parser/RdrHsSyn.lhs | 4 ++--
compiler/rename/RnSource.lhs | 8 ++++----
3 files changed, 12 insertions(+), 8 deletions(-)
diff --git a/compiler/hsSyn/HsDecls.lhs b/compiler/hsSyn/HsDecls.lhs
index f584372..a990d75 100644
--- a/compiler/hsSyn/HsDecls.lhs
+++ b/compiler/hsSyn/HsDecls.lhs
@@ -49,6 +49,7 @@ module HsDecls (
-- ** @default@ declarations
DefaultDecl(..), LDefaultDecl,
-- ** Template haskell declaration splice
+ SpliceExplicitFlag(..),
SpliceDecl(..), LSpliceDecl,
-- ** Foreign function interface declarations
ForeignDecl(..), LForeignDecl, ForeignImport(..), ForeignExport(..),
@@ -291,12 +292,15 @@ instance OutputableBndr name => Outputable (HsGroup name) where
vcat_mb gap (Nothing : ds) = vcat_mb gap ds
vcat_mb gap (Just d : ds) = gap $$ d $$ vcat_mb blankLine ds
+data SpliceExplicitFlag = ExplicitSplice | -- <=> $(f x y)
+ ImplicitSplice -- <=> f x y, i.e. a naked top level expression
+ deriving (Data, Typeable)
+
type LSpliceDecl name = Located (SpliceDecl name)
data SpliceDecl id
= SpliceDecl -- Top level splice
(Located (HsSplice id))
- HsExplicitFlag -- Explicit <=> $(f x y)
- -- Implicit <=> f x y, i.e. a naked top level expression
+ SpliceExplicitFlag
deriving (Typeable)
deriving instance (DataId id) => Data (SpliceDecl id)
diff --git a/compiler/parser/RdrHsSyn.lhs b/compiler/parser/RdrHsSyn.lhs
index b13251c..823be85 100644
--- a/compiler/parser/RdrHsSyn.lhs
+++ b/compiler/parser/RdrHsSyn.lhs
@@ -256,8 +256,8 @@ mkSpliceDecl :: LHsExpr RdrName -> HsDecl RdrName
mkSpliceDecl lexpr@(L loc expr)
| HsQuasiQuoteE qq <- expr = QuasiQuoteD qq
| HsSpliceE is_typed splice <- expr = ASSERT( not is_typed )
- SpliceD (SpliceDecl (L loc splice) Explicit)
- | otherwise = SpliceD (SpliceDecl (L loc splice) Implicit)
+ SpliceD (SpliceDecl (L loc splice) ExplicitSplice)
+ | otherwise = SpliceD (SpliceDecl (L loc splice) ImplicitSplice)
where
splice = mkHsSplice lexpr
diff --git a/compiler/rename/RnSource.lhs b/compiler/rename/RnSource.lhs
index 2dc71db..aa26b02 100644
--- a/compiler/rename/RnSource.lhs
+++ b/compiler/rename/RnSource.lhs
@@ -1471,10 +1471,10 @@ add gp loc (SpliceD splice@(SpliceDecl _ flag)) ds
= do { -- We've found a top-level splice. If it is an *implicit* one
-- (i.e. a naked top level expression)
case flag of
- Explicit -> return ()
- Implicit -> do { th_on <- xoptM Opt_TemplateHaskell
- ; unless th_on $ setSrcSpan loc $
- failWith badImplicitSplice }
+ ExplicitSplice -> return ()
+ ImplicitSplice -> do { th_on <- xoptM Opt_TemplateHaskell
+ ; unless th_on $ setSrcSpan loc $
+ failWith badImplicitSplice }
; return (gp, Just (splice, ds)) }
where
More information about the ghc-commits
mailing list