[Git][ghc/ghc][wip/jade/ast] hopefully fixes the assert error* and clears up some whitespace
Hassan Al-Awwadi (@hassan.awwadi)
gitlab at gitlab.haskell.org
Mon Sep 30 12:31:11 UTC 2024
Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC
Commits:
f3656886 by Hassan Al-Awwadi at 2024-09-30T14:30:43+02:00
hopefully fixes the assert error* and clears up some whitespace
*in GHC.Rename.HsType. I'm not certain but I also don't know what else it could be...
- - - - -
5 changed files:
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Rename/HsType.hs
Changes:
=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -598,7 +598,7 @@ data XXExprGhcTc
Int -- module-local tick number for True
Int -- module-local tick number for False
(LHsExpr GhcTc) -- sub-expression
-
+
| HsRecSelTc (FieldOcc GhcTc) -- ^ Variable pointing to record selector
-- See Note [Non-overloaded record field selectors] and
-- Note [Record selectors in the AST]
@@ -882,7 +882,7 @@ instance Outputable HsThingRn where
OrigExpr x -> ppr_builder "<OrigExpr>:" x
OrigStmt x -> ppr_builder "<OrigStmt>:" x
OrigPat x -> ppr_builder "<OrigPat>:" x
-
+
where ppr_builder prefix x = ifPprDebug (braces (text prefix <+> parens (ppr x))) (ppr x)
instance Outputable XXExprGhcRn where
=====================================
compiler/GHC/HsToCore/Expr.hs
=====================================
@@ -318,7 +318,7 @@ dsExpr e@(XExpr ext_expr_tc)
See the `HsApp` case for where it is filtered out
-}
- (HsRecSelTc (FieldOcc _ (L _ id))) ->
+ (HsRecSelTc (FieldOcc _ (L _ id))) ->
do { let name = getName id
RecSelId {sel_cons = (_, cons_wo_field)} = idDetails id
; cons_trimmed <- trim_cons cons_wo_field
=====================================
compiler/GHC/HsToCore/Ticks.hs
=====================================
@@ -602,7 +602,7 @@ addTickHsExpr (XExpr (HsTick t e)) =
liftM (XExpr . HsTick t) (addTickLHsExprNever e)
addTickHsExpr (XExpr (HsBinTick t0 t1 e)) =
liftM (XExpr . HsBinTick t0 t1) (addTickLHsExprNever e)
-
+
addTickHsExpr e@(XExpr (HsRecSelTc (FieldOcc _ id))) = do freeVar (unLoc id); return e
addTickHsExpr (HsDo srcloc cxt (L l stmts))
=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -1352,7 +1352,7 @@ instance HiePass p => ToHie (LocatedA (HsExpr (GhcPass p))) where
]
HsGetField {} -> []
HsProjection {} -> []
- XExpr x -> case hiePass @p of
+ XExpr x -> case hiePass @p of
HieTc -> case x of
WrapExpr w a
-> [ toHie $ L mspan a
@@ -1367,11 +1367,11 @@ instance HiePass p => ToHie (LocatedA (HsExpr (GhcPass p))) where
HsBinTick _ _ expr
-> [ toHie expr
]
- HsRecSelTc fld
+ HsRecSelTc fld
-> [ toHie $ RFC RecFieldOcc Nothing (L mspan fld)
]
- HieRn -> case x of
- HsRecSelRn fld
+ HieRn -> case x of
+ HsRecSelRn fld
-> [ toHie $ RFC RecFieldOcc Nothing (L mspan fld)
]
_ -> []
=====================================
compiler/GHC/Rename/HsType.hs
=====================================
@@ -1341,7 +1341,7 @@ rnField fl_env env (L l (ConDeclField _ names ty haddock_doc))
lookupField :: FastStringEnv FieldLabel -> FieldOcc GhcPs -> FieldOcc GhcRn
lookupField fl_env (FieldOcc _ (L lr rdr)) =
- FieldOcc rdr (L lr sel)
+ FieldOcc (mkRdrUnqual $ occName sel) (L lr sel)
where
lbl = occNameFS $ rdrNameOcc rdr
sel = flSelector
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3656886de845f36ecd9be6427cd9f715efbd127
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3656886de845f36ecd9be6427cd9f715efbd127
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/20240930/80c3a08b/attachment-0001.html>
More information about the ghc-commits
mailing list