[Git][ghc/ghc][wip/jade/ast] 2 commits: rename stuff
Hassan Al-Awwadi (@hassan.awwadi)
gitlab at gitlab.haskell.org
Tue Oct 1 09:48:03 UTC 2024
Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC
Commits:
6353a174 by Hassan Al-Awwadi at 2024-09-30T16:26:59+02:00
rename stuff
- - - - -
ec2c3223 by Hassan Al-Awwadi at 2024-10-01T11:47:38+02:00
cleaned remnant AmbiguousFieldOcc -> UpdFieldOcc
- - - - -
2 changed files:
- compiler/GHC/Tc/Gen/Head.hs
- utils/check-exact/ExactPrint.hs
Changes:
=====================================
compiler/GHC/Tc/Gen/Head.hs
=====================================
@@ -597,19 +597,19 @@ addHeadCtxt fun_ctxt thing_inside
tcInferRecSelId :: FieldOcc GhcRn
-> TcM ( (HsExpr GhcTc, TcSigmaType))
-tcInferRecSelId (FieldOcc sel_name (L l n))
+tcInferRecSelId (FieldOcc lbl (L l sel_name))
= do { sel_id <- tc_rec_sel_id
- ; let expr = XExpr (HsRecSelTc (FieldOcc sel_name (L l sel_id)))
+ ; let expr = XExpr (HsRecSelTc (FieldOcc lbl (L l sel_id)))
; return $ (expr, idType sel_id)
}
where
occ :: OccName
- occ = nameOccName n
+ occ = nameOccName sel_name
tc_rec_sel_id :: TcM TcId
-- Like tc_infer_id, but returns an Id not a HsExpr,
-- so we can wrap it back up into a HsRecSel
tc_rec_sel_id
- = do { thing <- tcLookup n
+ = do { thing <- tcLookup sel_name
; case thing of
ATcId { tct_id = id }
-> do { check_naughty occ id -- See Note [Local record selectors]
=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -53,6 +53,7 @@ import GHC.Utils.Outputable hiding ( (<>) )
import GHC.Utils.Panic
import Language.Haskell.Syntax.Basic (FieldLabelString(..))
+import Language.Haskell.Syntax.Types (UpdFieldOcc(..), FieldOcc(..))
import Control.Monad (forM, when, unless)
import Control.Monad.Identity (Identity(..))
@@ -4591,11 +4592,10 @@ instance ExactPrint (FieldOcc GhcPs) where
-- ---------------------------------------------------------------------
-instance ExactPrint (AmbiguousFieldOcc GhcPs) where
+instance ExactPrint (UpdFieldOcc GhcPs) where
getAnnotationEntry = const NoEntryVal
setAnnotationAnchor a _ _ _ = a
- exact f@(Unambiguous _ n) = markAnnotated n >> return f
- exact f@(Ambiguous _ n) = markAnnotated n >> return f
+ exact f@(UpdFieldOcc _ n) = markAnnotated n >> return f
-- ---------------------------------------------------------------------
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/484fba49b0698a1b7c8de90d98a786d5f55b7814...ec2c3223e7261ba39462cce8bc883d041eff031a
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/484fba49b0698a1b7c8de90d98a786d5f55b7814...ec2c3223e7261ba39462cce8bc883d041eff031a
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/20241001/2566112b/attachment-0001.html>
More information about the ghc-commits
mailing list