Skip to content

Commit

Permalink
Run untyped splices in the renamer.
Browse files Browse the repository at this point in the history
  • Loading branch information
mainland committed May 16, 2013
1 parent 4e99637 commit 74ac368
Show file tree
Hide file tree
Showing 9 changed files with 492 additions and 224 deletions.
1 change: 1 addition & 0 deletions compiler/deSugar/DsExpr.lhs
Expand Up @@ -557,6 +557,7 @@ Here is where we desugar the Template Haskell brackets and escapes
\begin{code}
-- Template Haskell stuff
dsExpr (HsRnBracketOut _ _) = panic "dsExpr HsRnBracketOut"
#ifdef GHCI
dsExpr (HsBracketOut x ps) = dsBracket x ps
#else
Expand Down
2 changes: 1 addition & 1 deletion compiler/deSugar/DsMeta.hs
Expand Up @@ -74,7 +74,7 @@ dsBracket :: HsBracket Name -> [PendingSplice] -> DsM CoreExpr
dsBracket brack splices
= dsExtendMetaEnv new_bit (do_brack brack)
where
new_bit = mkNameEnv [(n, Splice (unLoc e)) | (n,e) <- splices]
new_bit = mkNameEnv [(n, Splice (unLoc e)) | PendingTcSplice n e <- splices]

do_brack (VarBr _ n) = do { MkC e1 <- lookupOcc n ; return e1 }
do_brack (ExpBr e) = do { MkC e1 <- repLE e ; return e1 }
Expand Down
70 changes: 62 additions & 8 deletions compiler/hsSyn/HsExpr.lhs
Expand Up @@ -236,6 +236,13 @@ data HsExpr id
| HsBracket (HsBracket id)
-- See Note [Pending Renamer Splices]
| HsRnBracketOut (HsBracket Name) -- Output of the renamer is
-- the *original*
[PendingSplice] -- renamed expression, plus
-- _renamed_ splices to be
-- type checked
| HsBracketOut (HsBracket Name) -- Output of the type checker is
-- the *original*
[PendingSplice] -- renamed expression, plus
Expand Down Expand Up @@ -327,11 +334,50 @@ tupArgPresent :: HsTupArg id -> Bool
tupArgPresent (Present {}) = True
tupArgPresent (Missing {}) = False
type PendingSplice = (Name, LHsExpr Id) -- Typechecked splices, waiting to be
-- pasted back in by the desugarer
-- See Note [Pending Splices]
data PendingSplice
= PendingRnExpSplice Name (LHsExpr Name)
| PendingRnTypeSplice Name (LHsExpr Name)
| PendingRnCrossStageSplice Name
| PendingTcSplice Name (LHsExpr Id)
deriving (Data, Typeable)
\end{code}

Note [Pending Splices]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

Now that untyped brackets are not type checked, we need a mechanism to ensure
that splices contained in untyped brackets *are* type checked. Therefore the
renamer now renames every HsBracket into a HsRnBracketOut, which contains the
splices that need to be type checked. There are three varieties of pending
splices generated by the renamer:

* Pending expression splices (PendingRnExpSplice), e.g.,

[|$(f x) + 2|]

* Pending type splices (PendingRnTypeSplice), e.g.,

[|f :: $(g x)|]

* Pending cross-stage splices (PendingRnCrossStageSplice), e.g.,

\x -> [| x |]

There is a fourth variety of pending splice, which is generated by the type
checker:

* Pending *typed* expression splices, (PendingTcSplice), e.g.,

[||1 + $$(f 2)||]

It would be possible to eliminate HsRnBracketOut and use HsBracketOut for the
output of the renamer. However, when pretty printing the output of the renamer,
e.g., in a type error message, we *do not* want to print out the pending
splices. In contrast, when pretty printing the output of the type checker, we
*do* want to print the pending splices. So splitting them up seems to make
sense, although I hate to add another constructor to HsExpr.

Note [Parens in HsSyn]
~~~~~~~~~~~~~~~~~~~~~~
HsPar (and ParPat in patterns, HsParTy in types) is used as follows
Expand Down Expand Up @@ -536,11 +582,12 @@ ppr_expr (HsSCC lbl expr)
ppr_expr (HsWrap co_fn e) = pprHsWrapper (pprExpr e) co_fn
ppr_expr (HsType id) = ppr id
ppr_expr (HsSpliceE s) = pprSplice s
ppr_expr (HsBracket b) = pprHsBracket b
ppr_expr (HsBracketOut e []) = ppr e
ppr_expr (HsBracketOut e ps) = ppr e $$ ptext (sLit "pending") <+> ppr ps
ppr_expr (HsQuasiQuoteE qq) = ppr qq
ppr_expr (HsSpliceE s) = pprSplice s
ppr_expr (HsBracket b) = pprHsBracket b
ppr_expr (HsRnBracketOut e _) = ppr e
ppr_expr (HsBracketOut e []) = ppr e
ppr_expr (HsBracketOut e ps) = ppr e $$ ptext (sLit "pending") <+> ppr ps
ppr_expr (HsQuasiQuoteE qq) = ppr qq
ppr_expr (HsProc pat (L _ (HsCmdTop cmd _ _ _)))
= hsep [ptext (sLit "proc"), ppr pat, ptext (sLit "->"), ppr cmd]
Expand Down Expand Up @@ -622,6 +669,7 @@ hsExprNeedsParens (ExplicitList {}) = False
hsExprNeedsParens (ExplicitPArr {}) = False
hsExprNeedsParens (HsPar {}) = False
hsExprNeedsParens (HsBracket {}) = False
hsExprNeedsParens (HsRnBracketOut {}) = False
hsExprNeedsParens (HsBracketOut _ []) = False
hsExprNeedsParens (HsDo sc _ _)
| isListCompExpr sc = False
Expand Down Expand Up @@ -1362,6 +1410,12 @@ thBrackets pp_kind pp_body = char '[' <> pp_kind <> char '|' <+>
thTyBrackets :: SDoc -> SDoc
thTyBrackets pp_body = ptext (sLit "[||") <+> pp_body <+> ptext (sLit "||]")
instance Outputable PendingSplice where
ppr (PendingRnExpSplice name expr) = ppr (name, expr)
ppr (PendingRnTypeSplice name expr) = ppr (name, expr)
ppr (PendingRnCrossStageSplice name) = ppr name
ppr (PendingTcSplice name expr) = ppr (name, expr)
\end{code}
%************************************************************************
Expand Down
9 changes: 8 additions & 1 deletion compiler/rename/RnExpr.lhs
Expand Up @@ -110,7 +110,14 @@ rnExpr (HsVar v)
-- OverloadedLists works correctly
-> rnExpr (ExplicitList placeHolderType Nothing [])
| otherwise
-> finishHsVar name } }
-> do { mb_bind_lvl <- lookupLocalOccThLvl_maybe v
; case mb_bind_lvl of
{ Nothing -> return ()
; Just bind_lvl
| isExternalName name -> return ()
| otherwise -> checkThLocalName name bind_lvl
}
; finishHsVar name }}}
rnExpr (HsIPVar v)
= return (HsIPVar v, emptyFVs)
Expand Down

0 comments on commit 74ac368

Please sign in to comment.