[commit: ghc] wip/orf-reboot: Comments only (f23c72e)

git at git.haskell.org git at git.haskell.org
Mon Oct 12 06:37:18 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/orf-reboot
Link       : http://ghc.haskell.org/trac/ghc/changeset/f23c72ec6a51d6435b7f869018fc71d7f2866bc4/ghc

>---------------------------------------------------------------

commit f23c72ec6a51d6435b7f869018fc71d7f2866bc4
Author: Adam Gundry <adam at well-typed.com>
Date:   Tue Oct 6 16:36:55 2015 +0100

    Comments only


>---------------------------------------------------------------

f23c72ec6a51d6435b7f869018fc71d7f2866bc4
 compiler/hsSyn/HsPat.hs   | 47 +++++++++++++++++++++++++++--------------------
 compiler/hsSyn/HsTypes.hs |  8 ++++++++
 compiler/rename/RnPat.hs  |  1 -
 3 files changed, 35 insertions(+), 21 deletions(-)

diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs
index 2b44950..b37d836 100644
--- a/compiler/hsSyn/HsPat.hs
+++ b/compiler/hsSyn/HsPat.hs
@@ -286,18 +286,24 @@ data HsRecField' id arg = HsRecField {
 --    T { A.x } means T { A.x = x }
 
 
--- TODO update note
--- Note [HsRecUpdField selector]
--- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-
--- A HsRecUpdField always contains a label (in hsRecUpdFieldLbl)
--- giving the thing the user wrote, but thanks to
--- DuplicateRecordFields this may not unambiguously correspond to
--- a Name.  The hsRecUpdFieldSel is filled in by the renamer
--- (RnPat.rnHsRecUpdFields) to contain a list of the candidate
--- selector function names.  The typechecker (tcExpr) then
--- disambiguates the record update, so after the typechecker the list
--- will always be a singleton.
+-- Note [HsRecField and HsRecUpdField]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+-- A HsRecField (used for record construction and pattern matching)
+-- contains an unambiguous occurrence of a field (i.e. a FieldOcc).
+-- We can't just store the Name, because thanks to
+-- DuplicateRecordFields this may not correspond to the label the user
+-- wrote.
+--
+-- A HsRecUpdField (used for record update) contains a potentially
+-- ambiguous occurrence of a field (an AmbiguousFieldOcc).  The
+-- renamer will fill in the selector function if it can, but if the
+-- selector is ambiguous the renamer will defer to the typechecker.
+-- After the typechecker, a unique selector will have been determined.
+--
+-- The renamer produces an Unambiguous result if it can, rather than
+-- just doing the lookup in the typechecker, so that completely
+-- unambiguous updates can be represented by 'DsMeta.repUpdFields'.
 --
 -- For example, suppose we have:
 --
@@ -306,17 +312,18 @@ data HsRecField' id arg = HsRecField {
 --
 --     f z = (z { x = 3 }) :: S
 --
--- After the renamer, the HsRecUpdField corresponding to the record
--- update will have
+-- The parsed HsRecUpdField corresponding to the record update will have:
+--
+--     hsRecFieldLbl = Unambiguous "x" PlaceHolder :: AmbiguousFieldOcc RdrName
+--
+-- After the renamer, this will become:
 --
---     hsRecUpdFieldLbl = "x"
---     hsRecUpdFieldSel = [$sel:x:MkS, $sel:x:MkT]
+--     hsRecFieldLbl = Ambiguous   "x" PlaceHolder :: AmbiguousFieldOcc Name
 --
--- and the typechecker will determine that $sel:x:MkS is meant.
+-- (note that the Unambiguous constructor is not type-correct here).
+-- The typechecker will determine the particular selector:
 --
--- We fill in hsRecUpdFieldSel in the renamer, rather than just doing
--- the lookup in the typechecker, so that completely unambiguous
--- updates can be represented by 'DsMeta.repUpdFields'.
+--     hsRecFieldLbl = Unambiguous "x" $sel:x:MkS  :: AmbiguousFieldOcc Id
 
 hsRecFields :: HsRecFields id arg -> [PostRn id id]
 hsRecFields rbinds = map (unLoc . hsRecFieldSel . unLoc) (rec_flds rbinds)
diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/hsSyn/HsTypes.hs
index d882146..22ad00b 100644
--- a/compiler/hsSyn/HsTypes.hs
+++ b/compiler/hsSyn/HsTypes.hs
@@ -578,6 +578,14 @@ mkFieldOcc :: RdrName -> FieldOcc RdrName
 mkFieldOcc rdr = FieldOcc rdr PlaceHolder
 
 
+-- | Represents an *occurrence* of a field that is potentially
+-- ambiguous after the renamer, with the ambiguity resolved by the
+-- typechecker.  We always store the 'RdrName' that the user
+-- originally wrote, and store the selector function after the renamer
+-- (for unambiguous occurrences) or the typechecker (for ambiguous
+-- occurrences).
+--
+-- See Note [HsRecField and HsRecUpdField] in HsPat
 data AmbiguousFieldOcc name
   = Unambiguous RdrName (PostRn name name)
   | Ambiguous   RdrName (PostTc name name)
diff --git a/compiler/rename/RnPat.hs b/compiler/rename/RnPat.hs
index 8ef484a..115e4d5 100644
--- a/compiler/rename/RnPat.hs
+++ b/compiler/rename/RnPat.hs
@@ -648,7 +648,6 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot })
     (_, dup_flds) = removeDups compare (getFieldLbls flds)
 
 
--- TODO unduplicate?
 rnHsRecUpdFields
     :: [LHsRecUpdField RdrName]
     -> RnM ([LHsRecUpdField Name], FreeVars)



More information about the ghc-commits mailing list