diff options
author | Shayne Fletcher <shayne@shaynefletcher.org> | 2021-04-24 16:59:26 -0400 |
---|---|---|
committer | Shayne Fletcher <shayne@shaynefletcher.org> | 2021-05-23 08:02:58 +1000 |
commit | 0b1eed74e8ad5194152ed656ac3e4a547726b70a (patch) | |
tree | 3e654267d7077050a2358910ebe0ef29cfdddb0d /compiler/Language/Haskell/Syntax | |
parent | ef4d2999a200f22c864d7c1a2bdfbfd726a0f849 (diff) | |
download | haskell-0b1eed74e8ad5194152ed656ac3e4a547726b70a.tar.gz |
Change representation of field selector occurences
- Change the names of the fields in in `data FieldOcc`
- Renames `HsRecFld` to `HsRecSel`
- Replace `AmbiguousFieldOcc p` in `HsRecSel` with `FieldOcc p`
- Contains a haddock submodule update
The primary motivation of this change is to remove
`AmbiguousFieldOcc`. This is one of a suite of changes improving how
record syntax (most notably record update syntax) is represented in
the AST.
Diffstat (limited to 'compiler/Language/Haskell/Syntax')
-rw-r--r-- | compiler/Language/Haskell/Syntax/Binds.hs | 3 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Expr.hs | 64 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Extension.hs | 2 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Pat.hs | 2 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Type.hs | 49 |
5 files changed, 86 insertions, 34 deletions
diff --git a/compiler/Language/Haskell/Syntax/Binds.hs b/compiler/Language/Haskell/Syntax/Binds.hs index 8c69f10eb8..60ca3fad1b 100644 --- a/compiler/Language/Haskell/Syntax/Binds.hs +++ b/compiler/Language/Haskell/Syntax/Binds.hs @@ -33,6 +33,7 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Pat import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Type +import GHC.Types.Name.Reader(RdrName) import GHC.Tc.Types.Evidence import GHC.Core.Type import GHC.Types.Basic @@ -931,7 +932,7 @@ when we have a different name for the local and top-level binder, making the distinction between the two names clear. -} -instance Outputable (RecordPatSynField a) where +instance Outputable (XRec a RdrName) => Outputable (RecordPatSynField a) where ppr (RecordPatSynField { recordPatSynField = v }) = ppr v diff --git a/compiler/Language/Haskell/Syntax/Expr.hs b/compiler/Language/Haskell/Syntax/Expr.hs index a9592304e6..6f5150a1b4 100644 --- a/compiler/Language/Haskell/Syntax/Expr.hs +++ b/compiler/Language/Haskell/Syntax/Expr.hs @@ -267,6 +267,55 @@ is Less Cool because typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.) -} +{- +Note [Record selectors in the AST] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Here is how record selectors are expressed in GHC's AST: + +Example data type + data T = MkT { size :: Int } + +Record selectors: + | GhcPs | GhcRn | GhcTc | +----------------------------------------------------------------------------------| +size (assuming one | HsVar | HsRecSel | HsRecSel | + 'size' in scope) | | | | +----------------------|--------------|----------------------|---------------------| +.size (assuming | HsProjection | getField @"size" | getField @"size" | + OverloadedRecordDot) | | | | +----------------------|--------------|----------------------|---------------------| +e.size (assuming | HsGetField | getField @"size" e | getField @"size" e | + OverloadedRecordDot) | | | | + +NB 1: DuplicateRecordFields makes no difference to the first row of +this table, except that if 'size' is a field of more than one data +type, then a naked use of the record selector 'size' may well be +ambiguous. You have to use a qualified name. And there is no way to do +this if both data types are declared in the same module. + +NB 2: The notation getField @"size" e is short for +HsApp (HsAppType (HsVar "getField") (HsWC (HsTyLit (HsStrTy "size")) [])) e. +We track the original parsed syntax via HsExpanded. + +-} + +{- +Note [Non-overloaded record field selectors] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + data T = MkT { x,y :: Int } + f r x = x + y r + +This parses with HsVar for x, y, r on the RHS of f. Later, the renamer +recognises that y in the RHS of f is really a record selector, and +changes it to a HsRecSel. In contrast x is locally bound, shadowing +the record selector, and stays as an HsVar. + +The renamer adds the Name of the record selector into the XCFieldOcc +extension field, The typechecker keeps HsRecSel as HsRecSel, and +transforms the record-selector Name to an Id. +-} + -- | A Haskell expression. data HsExpr p = HsVar (XVar p) @@ -285,11 +334,10 @@ data HsExpr p -- solving. See Note [Holes] in GHC.Tc.Types.Constraint. - | HsRecFld (XRecFld p) - (AmbiguousFieldOcc p) -- ^ Variable pointing to record selector - -- The parser produces HsVars - -- The renamer renames record-field selectors to HsRecFld - -- The typechecker preserves HsRecFld + | HsRecSel (XRecSel p) + (FieldOcc p) -- ^ Variable pointing to record selector + -- See Note [Non-overloaded record field selectors] and + -- Note [Record selectors in the AST] | HsOverLabel (XOverLabel p) FastString -- ^ Overloaded label (Note [Overloaded labels] in GHC.OverloadedLabels) @@ -334,7 +382,7 @@ data HsExpr p -- NB Bracketed ops such as (+) come out as Vars. -- NB Sadly, we need an expr for the operator in an OpApp/Section since - -- the renamer may turn a HsVar into HsRecFld or HsUnboundVar + -- the renamer may turn a HsVar into HsRecSel or HsUnboundVar | OpApp (XOpApp p) (LHsExpr p) -- left operand @@ -486,7 +534,7 @@ data HsExpr p -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDot' -- -- This case only arises when the OverloadedRecordDot langauge - -- extension is enabled. + -- extension is enabled. See Note [Record Selectors in the AST]. | HsGetField { gf_ext :: XGetField p @@ -500,7 +548,7 @@ data HsExpr p -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnCloseP' -- -- This case only arises when the OverloadedRecordDot langauge - -- extensions is enabled. + -- extensions is enabled. See Note [Record Selectors in the AST]. | HsProjection { proj_ext :: XProjection p diff --git a/compiler/Language/Haskell/Syntax/Extension.hs b/compiler/Language/Haskell/Syntax/Extension.hs index 44695066d4..f414968a6e 100644 --- a/compiler/Language/Haskell/Syntax/Extension.hs +++ b/compiler/Language/Haskell/Syntax/Extension.hs @@ -385,7 +385,7 @@ type family XXInjectivityAnn x type family XVar x type family XUnboundVar x -type family XRecFld x +type family XRecSel x type family XOverLabel x type family XIPVar x type family XOverLitE x diff --git a/compiler/Language/Haskell/Syntax/Pat.hs b/compiler/Language/Haskell/Syntax/Pat.hs index 051f7d8f72..c7829d833c 100644 --- a/compiler/Language/Haskell/Syntax/Pat.hs +++ b/compiler/Language/Haskell/Syntax/Pat.hs @@ -344,7 +344,7 @@ hsRecFieldsArgs :: forall p arg. UnXRec p => HsRecFields p arg -> [arg] hsRecFieldsArgs rbinds = map (hfbRHS . unXRec @p) (rec_flds rbinds) hsRecFieldSel :: forall p arg. UnXRec p => HsRecField p arg -> XCFieldOcc p -hsRecFieldSel = extFieldOcc . unXRec @p . hfbLHS +hsRecFieldSel = foExt . unXRec @p . hfbLHS {- diff --git a/compiler/Language/Haskell/Syntax/Type.hs b/compiler/Language/Haskell/Syntax/Type.hs index 1b945c9c1e..1b311716d0 100644 --- a/compiler/Language/Haskell/Syntax/Type.hs +++ b/compiler/Language/Haskell/Syntax/Type.hs @@ -6,6 +6,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeApplications #-} {-# LANGUAGE UndecidableInstances #-} -- Wrinkle in Note [Trees That Grow] -- in module Language.Haskell.Syntax.Extension {- @@ -1293,31 +1294,34 @@ type LFieldOcc pass = XRec pass (FieldOcc pass) -- | Field Occurrence -- --- Represents an *occurrence* of an unambiguous field. This may or may not be a +-- Represents an *occurrence* of a field. This may or may not be a -- binding occurrence (e.g. this type is used in 'ConDeclField' and --- 'RecordPatSynField' which bind their fields, but also in 'HsRecField' for --- record construction and patterns, which do not). +-- 'RecordPatSynField' which bind their fields, but also in +-- 'HsRecField' for record construction and patterns, which do not). -- --- We store both the 'RdrName' the user originally wrote, and after the renamer, --- the selector function. -data FieldOcc pass = FieldOcc { extFieldOcc :: XCFieldOcc pass - , rdrNameFieldOcc :: LocatedN RdrName - -- ^ See Note [Located RdrNames] in "GHC.Hs.Expr" - } - - | XFieldOcc - !(XXFieldOcc pass) - -deriving instance (Eq (XCFieldOcc pass), Eq (XXFieldOcc pass)) => Eq (FieldOcc pass) +-- We store both the 'RdrName' the user originally wrote, and after +-- the renamer we use the extension field to store the selector +-- function. +data FieldOcc pass + = FieldOcc { + foExt :: XCFieldOcc pass + , foLabel :: XRec pass RdrName -- See Note [Located RdrNames] in Language.Haskell.Syntax.Expr + } + | XFieldOcc !(XXFieldOcc pass) +deriving instance ( + Eq (XRec pass RdrName) + , Eq (XCFieldOcc pass) + , Eq (XXFieldOcc pass) + ) => Eq (FieldOcc pass) -instance Outputable (FieldOcc pass) where - ppr = ppr . rdrNameFieldOcc +instance Outputable (XRec pass RdrName) => Outputable (FieldOcc pass) where + ppr = ppr . foLabel -instance OutputableBndr (FieldOcc pass) where - pprInfixOcc = pprInfixOcc . unLoc . rdrNameFieldOcc - pprPrefixOcc = pprPrefixOcc . unLoc . rdrNameFieldOcc +instance (UnXRec pass, OutputableBndr (XRec pass RdrName)) => OutputableBndr (FieldOcc pass) where + pprInfixOcc = pprInfixOcc . unXRec @pass . foLabel + pprPrefixOcc = pprPrefixOcc . unXRec @pass . foLabel -instance OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) where +instance (UnXRec pass, OutputableBndr (XRec pass RdrName)) => OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) where pprInfixOcc = pprInfixOcc . unLoc pprPrefixOcc = pprPrefixOcc . unLoc @@ -1333,9 +1337,8 @@ type LAmbiguousFieldOcc pass = XRec pass (AmbiguousFieldOcc pass) -- (for unambiguous occurrences) or the typechecker (for ambiguous -- occurrences). -- --- See Note [HsRecField and HsRecUpdField] in "GHC.Hs.Pat" and --- Note [Disambiguating record fields] in "GHC.Tc.Gen.Head". --- See Note [Located RdrNames] in "GHC.Hs.Expr" +-- See Note [HsRecField and HsRecUpdField] in "GHC.Hs.Pat". +-- See Note [Located RdrNames] in "GHC.Hs.Expr". data AmbiguousFieldOcc pass = Unambiguous (XUnambiguous pass) (LocatedN RdrName) | Ambiguous (XAmbiguous pass) (LocatedN RdrName) |