[Git][ghc/ghc][wip/aidylns/ttg-remove-hsunboundvar-via-hshole] 2 commits: Use rnUnboundVar in HsVar underscore case
Adriaan Leijnse (@aidylns)
gitlab at gitlab.haskell.org
Wed Nov 20 12:28:10 UTC 2024
Adriaan Leijnse pushed to branch wip/aidylns/ttg-remove-hsunboundvar-via-hshole at Glasgow Haskell Compiler / GHC
Commits:
78a161d3 by Adriaan Leijnse at 2024-11-20T12:26:00+00:00
Use rnUnboundVar in HsVar underscore case
- - - - -
bdaba97f by Adriaan Leijnse at 2024-11-20T12:26:32+00:00
Check for underscore equality in Parser
To keep the code as similar in behavior to the original HsUnboundVar
implementation as possible.
- - - - -
4 changed files:
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Tc/Gen/App.hs
Changes:
=====================================
compiler/GHC/Parser/Errors/Ppr.hs
=====================================
@@ -39,6 +39,7 @@ import Data.List.NonEmpty (NonEmpty((:|)))
import GHC.Hs.Pat (Pat(..), LPat)
import GHC.Hs.Extension
import GHC.Parser.Annotation (noAnn)
+import GHC.Types.Name (isUnderscore, HasOccName (..))
instance Diagnostic PsMessage where
@@ -842,7 +843,7 @@ instance Diagnostic PsMessage where
-- Sadly 'foreign import' still barfs 'parse error' because
-- 'import' is a keyword
-- looks_like :: RdrName -> LHsExpr GhcPsErr -> Bool -- AZ
- looks_like s (L _ (HsVar _ (L _ v))) = v == s
+ looks_like s (L _ (HsVar _ (L _ v))) | not (isUnderscore (occName v)) = v == s
looks_like s (L _ (HsApp _ lhs _)) = looks_like s lhs
looks_like _ _ = False
=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -1208,6 +1208,7 @@ checkContextExpr orig_expr@(L (EpAnn l _ cs) _) =
= check (opi ++ [open_tok], close_tok : cpi, csi) expr
check (oparens,cparens,cs) (L _ (HsVar _ (L (EpAnn _ (NameAnnOnly (NameParens open closed) []) _) name)))
| name == nameRdrName (dataConName unitDataCon)
+ , not (isUnderscore (occName name))
= mkCTuple (oparens ++ [open], closed : cparens, cs) []
check _ _ = unprocessed
@@ -2867,6 +2868,7 @@ mkRecConstrOrUpdate
-> PV (HsExpr GhcPs)
mkRecConstrOrUpdate _ (L _ (HsVar _ (L l c))) _lrec (fbinds,dd) anns
| isRdrDataCon c
+ , not (isUnderscore (occName c))
= do
let (fs, ps) = partitionEithers fbinds
case ps of
=====================================
compiler/GHC/Rename/Expr.hs
=====================================
@@ -321,12 +321,9 @@ rnUnboundVar (L l v) = do
uniq <- newUnique
return (HsVar (Unbound ()) (L l (mkUnboundNameRdr_ uniq v noSrcSpan)), emptyFVs)
-rnExpr (HsVar NoExtField (L l v))
+rnExpr (HsVar NoExtField lv@(L l v))
| isUnderscore (rdrNameOcc v)
- = do
- -- TODO: use rnUnboundVar/deduplicate?
- uniq <- newUnique
- return (HsVar (Unbound ()) (L l (mkUnboundNameRdr_ uniq v noSrcSpan)), emptyFVs)
+ = rnUnboundVar lv
rnExpr (HsVar NoExtField locatedRdrName@(L l v))
| otherwise
= do { dflags <- getDynFlags
=====================================
compiler/GHC/Tc/Gen/App.hs
=====================================
@@ -956,7 +956,7 @@ tcVDQ conc_tvs (tvb, inner_ty) arg
; tc_inst_forall_arg conc_tvs (tvb, inner_ty) hs_wc_ty }
-- Convert a HsExpr into the equivalent HsType.
--- See [RequiredTypeArguments and the T2T mapping]
+-- See Note [RequiredTypeArguments and the T2T mapping]
expr_to_type :: LHsExpr GhcRn -> TcM (LHsWcType GhcRn)
expr_to_type earg =
case stripParensLHsExpr earg of
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9eb5ce46901dbebf38e90f411e06b9c7e036c21f...bdaba97fe7dd32561402ac76a47775940ebb0bb0
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9eb5ce46901dbebf38e90f411e06b9c7e036c21f...bdaba97fe7dd32561402ac76a47775940ebb0bb0
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20241120/ed92c409/attachment-0001.html>
More information about the ghc-commits
mailing list