[commit: ghc] master: Add the rest of the notes for Located RdrName (e587217)

git at git.haskell.org git at git.haskell.org
Mon Nov 23 17:34:04 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/e587217b53a7bb1be1e629e3b71962142794b651/ghc

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

commit e587217b53a7bb1be1e629e3b71962142794b651
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date:   Mon Nov 23 19:33:34 2015 +0200

    Add the rest of the notes for Located RdrName


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

e587217b53a7bb1be1e629e3b71962142794b651
 compiler/hsSyn/HsExpr.hs   | 12 ++++++++++++
 compiler/hsSyn/HsImpExp.hs |  2 ++
 compiler/hsSyn/HsPat.hs    |  3 ++-
 compiler/hsSyn/HsTypes.hs  |  3 ++-
 4 files changed, 18 insertions(+), 2 deletions(-)

diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs
index af38f4b..7106b06 100644
--- a/compiler/hsSyn/HsExpr.hs
+++ b/compiler/hsSyn/HsExpr.hs
@@ -129,6 +129,8 @@ is Less Cool because
 data HsExpr id
   = HsVar     (Located id)   -- ^ Variable
 
+                             -- See Note [Located RdrNames]
+
   | HsUnboundVar OccName     -- ^ Unbound variable; also used for "holes" _, or _x.
                              -- Turned from HsVar to HsUnboundVar by the renamer, when
                              --   it finds an out-of-scope variable
@@ -592,6 +594,16 @@ P x = P False
 hence we need to provide the correct dictionaries to P on the RHS so that we can
 build the expression.
 
+Note [Located RdrNames]
+~~~~~~~~~~~~~~~~~~~~~~~
+A number of syntax elements have seemingly redundant locations attached to them.
+This is deliberate, to allow transformations making use of the API Annotations
+to easily correlate a Located Name in the RenamedSource with a Located RdrName
+in the ParsedSource.
+
+There are unfortunately enough differences between the ParsedSource and the
+RenamedSource that the API Annotations cannot be used directly with
+RenamedSource, so this allows a simple mapping to be used based on the location.
 -}
 
 instance OutputableBndr id => Outputable (HsExpr id) where
diff --git a/compiler/hsSyn/HsImpExp.hs b/compiler/hsSyn/HsImpExp.hs
index 429755e..b854b98 100644
--- a/compiler/hsSyn/HsImpExp.hs
+++ b/compiler/hsSyn/HsImpExp.hs
@@ -141,11 +141,13 @@ data IE name
         --             'ApiAnnotation.AnnType'
 
         -- For details on above see note [Api annotations] in ApiAnnotation
+        -- See Note [Located RdrNames] in HsExpr
   | IEThingAbs  (Located name)     -- ^ Class/Type (can't tell)
         --  - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnPattern',
         --             'ApiAnnotation.AnnType','ApiAnnotation.AnnVal'
 
         -- For details on above see note [Api annotations] in ApiAnnotation
+        -- See Note [Located RdrNames] in HsExpr
   | IEThingAll  (Located name)     -- ^ Class/Type plus all methods/constructors
         --
         -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen',
diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs
index 6d29ddf..3209562 100644
--- a/compiler/hsSyn/HsPat.hs
+++ b/compiler/hsSyn/HsPat.hs
@@ -74,7 +74,8 @@ data Pat id
         -- The sole reason for a type on a WildPat is to
         -- support hsPatType :: Pat Id -> Type
 
-  | VarPat      (Located id)            -- Variable
+  | VarPat      (Located id) -- Variable
+                             -- See Note [Located RdrNames] in HsExpr
   | LazyPat     (LPat id)               -- Lazy pattern
     -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnTilde'
 
diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/hsSyn/HsTypes.hs
index e1ea86b..3fea396 100644
--- a/compiler/hsSyn/HsTypes.hs
+++ b/compiler/hsSyn/HsTypes.hs
@@ -226,7 +226,7 @@ instance OutputableBndr HsIPName where
 data HsTyVarBndr name
   = UserTyVar        -- no explicit kinding
          (Located name)
-
+        -- See Note [Located RdrNames] in HsExpr
   | KindedTyVar
          (Located name)
          (LHsKind name)  -- The user-supplied kind signature
@@ -268,6 +268,7 @@ data HsType name
   | HsTyVar    (Located name)
                   -- Type variable, type constructor, or data constructor
                   -- see Note [Promotions (HsTyVar)]
+                  -- See Note [Located RdrNames] in HsExpr
       -- ^ - 'ApiAnnotation.AnnKeywordId' : None
 
       -- For details on above see note [Api annotations] in ApiAnnotation



More information about the ghc-commits mailing list