Remove RdrName from AST
This merge furthers #21592.
Currently we have
module Language.Haskell.Syntax.Type where
import GHC.Types.Name.Reader ( RdrName )
data FieldOcc pass
= FieldOcc {
foExt :: XCFieldOcc pass
, foLabel :: XRec pass RdrName
}
with the following type family instantiations.
module GHC.Hs.Type.hs where
type instance XCFieldOcc GhcPs = NoExtField
type instance XCFieldOcc GhcRn = Name
type instance XCFieldOcc GhcTc = Id
FieldOcc is a datatype that represents a field occurrence like field record
or field { record = x }
(which can be a getter or a setter). This type is used in the Haskell Syntax, and yet it refers directly to RdrName which it imports from GHC.Types.Name.Reader
. To fix this we move the RdrName from the foLabel to the foExt field by setting type instance XCFieldOcc GhcRn/GhcTc = RdrName
. What about foLabel, well, it can store the actual label as it moves through the Ghc Passes. foLabel :: LIdP pass
, so it goes RdrName -> Name -> Id.
So the RdrName starts in the foLabel during the Parse pass, when it is actually the label, and moves to the extension field when it becomes a purely GHC thing used for exact printing.
so now we have:
module Language.Haskell.Syntax.Type where
data FieldOcc pass
= FieldOcc {
foExt :: XCFieldOcc pass
, foLabel :: LIdP pass
}
module GHC.Hs.Type.hs where
type instance XCFieldOcc GhcPs = NoExtField -- RdrName is stored in the proper IdP field
type instance XCFieldOcc GhcRn = RdrName
type instance XCFieldOcc GhcTc = RdrName
Nice. Language.Haskell.Syntax.Type
no longer needs to import GHC.Types.Name.Reader
, mission successful. Of course everywhere were we used to refer to foExt we now need to refer to foLabel instead, and vice versa, but that's just churn.
Two more things have changed:
data HsExpr = ...
| HsRecSel (XRecSel p)
(FieldOcc p) -- ^ Variable pointing to record selector
-- See Note [Non-overloaded record field selectors] and
-- Note [Record selectors in the AST]
well this constructor is purely made by the renamer, its not actually part of the haskell syntax at all, so it has been moved to the extension constructors of HsExpr GhcRn
and HsExpr GhcTc
(XXExprGhcRn
and XXExprGhcTc
, respectively). This doesn't cut an edge but it does mean L.H.S more properly represents the actual syntax of haskell now.
The final one is truly independent of the entire L.H.S story, but still worthwhile, we've changed the FieldOcc/AmbiguousFieldOcc story a bit. Largely we've simplified it. Remember how above I mentioned the field { record = x }
syntax for updating a value? well if there are two types with the same fieldname, like Player { x :: Int, ... }
and Monster { x :: Int, ... }
, then an update like entity { x = 5 }
is ambiguous, and when the renaming pass shows up it can't actually rename it to a fully qualified name. Then, later, during type checking, we can actually resolve this through "type-directed disambiguation", a well known monstrous hack. So there used to be an entire song and dance with different types and constructors that only existed during different passes but could theoretically exist whenever. We've simplified all that, now there is only one type FieldOcc
, and if we can't disambiguate it during the rename pass, we just make an mkUnboundName and during typechecking it all works out anyway.
Once type directed disambiguation is gone, this wart can (and should) be removed with it. When it'll be gone, however, remains unknown for now.