summaryrefslogtreecommitdiff
path: root/compiler/Language/Haskell/Syntax
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/Language/Haskell/Syntax')
-rw-r--r--compiler/Language/Haskell/Syntax/Binds.hs3
-rw-r--r--compiler/Language/Haskell/Syntax/Expr.hs24
-rw-r--r--compiler/Language/Haskell/Syntax/Pat.hs2
-rw-r--r--compiler/Language/Haskell/Syntax/Type.hs49
4 files changed, 49 insertions, 29 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 e7756cc804..17a0929976 100644
--- a/compiler/Language/Haskell/Syntax/Expr.hs
+++ b/compiler/Language/Haskell/Syntax/Expr.hs
@@ -265,6 +265,24 @@ is Less Cool because
typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.)
-}
+{-
+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. Then, if
+-XOverloadedRecordFields is /off/, the renamer recognises that y in
+the RHS of f is really a record selector, and changes it to a
+HsRecFld. In contrast x is locally bound, shadowing the record
+selector, and stay as an HsVar.
+
+The renamer adds the Name of the record selector into the XRecFld
+extension field, The typechecker keeps HsRecFld as HsRecFld, and
+transforms the record-selector Name to an Id.
+-}
+
-- | A Haskell expression.
data HsExpr p
= HsVar (XVar p)
@@ -287,10 +305,8 @@ data HsExpr p
-- HsVar for pretty printing
| 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
+ (FieldOcc p) -- ^ Variable pointing to record selector
+ -- See Note [Non-overloaded record field selectors]
| HsOverLabel (XOverLabel p) FastString
-- ^ Overloaded label (Note [Overloaded labels] in GHC.OverloadedLabels)
diff --git a/compiler/Language/Haskell/Syntax/Pat.hs b/compiler/Language/Haskell/Syntax/Pat.hs
index 4417026478..a7fb5d8640 100644
--- a/compiler/Language/Haskell/Syntax/Pat.hs
+++ b/compiler/Language/Haskell/Syntax/Pat.hs
@@ -345,7 +345,7 @@ hsRecFieldsArgs :: forall p arg. UnXRec p => HsRecFields p arg -> [arg]
hsRecFieldsArgs rbinds = map (hsRecFieldArg . unXRec @p) (rec_flds rbinds)
hsRecFieldSel :: HsRecField pass arg -> Located (XCFieldOcc pass)
-hsRecFieldSel = fmap extFieldOcc . hsRecFieldLbl
+hsRecFieldSel = fmap foExt . hsRecFieldLbl
{-
diff --git a/compiler/Language/Haskell/Syntax/Type.hs b/compiler/Language/Haskell/Syntax/Type.hs
index f23072c04a..f7ebe42da0 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
{-
@@ -1248,31 +1249,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
@@ -1285,9 +1289,8 @@ instance OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) where
-- (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)