[commit: ghc] wip/orf-reboot: Get rid of hsRecFieldSel landmine, the stupid way (282a23d)

git at git.haskell.org git at git.haskell.org
Fri Mar 27 15:46:18 UTC 2015


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

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

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

commit 282a23d250e349574067bdbb787027214a828d29
Author: Adam Gundry <adam at well-typed.com>
Date:   Mon Feb 23 14:57:17 2015 +0000

    Get rid of hsRecFieldSel landmine, the stupid way


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

282a23d250e349574067bdbb787027214a828d29
 compiler/hsSyn/Convert.hs | 4 ++--
 compiler/hsSyn/HsPat.hs   | 7 +++++--
 2 files changed, 7 insertions(+), 4 deletions(-)

diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs
index 33a1165..6202703 100644
--- a/compiler/hsSyn/Convert.hs
+++ b/compiler/hsSyn/Convert.hs
@@ -725,7 +725,7 @@ cvtFld :: (TH.Name, TH.Exp) -> CvtM (LHsRecField RdrName (LHsExpr RdrName))
 cvtFld (v,e)
   = do  { v' <- vNameL v; e' <- cvtl e
         ; return (noLoc $ HsRecField { hsRecFieldLbl = v'
-                                     , hsRecFieldSel = hsRecFieldSelMissing -- AMG TODO
+                                     , hsRecFieldSel = hsRecFieldSelMissing
                                      , hsRecFieldArg = e'
                                      , hsRecPun = False}) }
 
@@ -944,7 +944,7 @@ cvtPatFld :: (TH.Name, TH.Pat) -> CvtM (LHsRecField RdrName (LPat RdrName))
 cvtPatFld (s,p)
   = do  { s' <- vNameL s; p' <- cvtPat p
         ; return (noLoc $ HsRecField { hsRecFieldLbl = s'
-                                     , hsRecFieldSel = hsRecFieldSelMissing -- AMG TODO
+                                     , hsRecFieldSel = hsRecFieldSelMissing
                                      , hsRecFieldArg = p'
                                      , hsRecPun = False}) }
 
diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs
index e2baac1..2c72855 100644
--- a/compiler/hsSyn/HsPat.hs
+++ b/compiler/hsSyn/HsPat.hs
@@ -309,10 +309,13 @@ data HsRecField id arg = HsRecField {
 --     hsRecFieldSel = Right [(S, $sel:x:S), (T, $sel:x:T)]
 --
 -- and the typechecker will determine that $sel:x:S is meant.
-
+--
+-- AMG TODO: it would be nice if we could enforce in the types that
+-- ambiguous fields occur only in record updates, and only between the
+-- renamer and the typechecker.
 
 hsRecFieldSelMissing :: Either id [(id, id)]
-hsRecFieldSelMissing = error "hsRecFieldSelMissing"
+hsRecFieldSelMissing = Right []
 
 hsRecFields :: HsRecFields id arg -> [(FieldLabelString, Either id [(id, id)])]
 hsRecFields rbinds = map (toFld . unLoc) (rec_flds rbinds)



More information about the ghc-commits mailing list