[commit: ghc] wip/orf-reboot: Make parser report use of .. in record updates (653aee2)
git at git.haskell.org
git at git.haskell.org
Tue Jul 14 20:53:17 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/orf-reboot
Link : http://ghc.haskell.org/trac/ghc/changeset/653aee2163a39ae8db6bc290778defe68a98224d/ghc
>---------------------------------------------------------------
commit 653aee2163a39ae8db6bc290778defe68a98224d
Author: Adam Gundry <adam at well-typed.com>
Date: Tue Jul 14 20:39:19 2015 +0100
Make parser report use of .. in record updates
>---------------------------------------------------------------
653aee2163a39ae8db6bc290778defe68a98224d
compiler/parser/RdrHsSyn.hs | 5 +++--
compiler/rename/RnPat.hs | 14 ++++----------
2 files changed, 7 insertions(+), 12 deletions(-)
diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs
index be0cf1b..ab3207f 100644
--- a/compiler/parser/RdrHsSyn.hs
+++ b/compiler/parser/RdrHsSyn.hs
@@ -1179,8 +1179,9 @@ mkRecConstrOrUpdate
mkRecConstrOrUpdate (L l (HsVar c)) _ (fs,dd)
| isRdrDataCon c
= return (RecordCon (L l c) noPostTcExpr (mk_rec_fields fs dd))
-mkRecConstrOrUpdate exp _ (fs,dd)
- = return (RecordUpd exp (map (fmap mk_rec_upd_field) fs) [] [] [])
+mkRecConstrOrUpdate exp@(L l _) _ (fs,dd)
+ | dd = parseErrorSDoc l (text "You cannot use `..' in a record update")
+ | otherwise = return (RecordUpd exp (map (fmap mk_rec_upd_field) fs) [] [] [])
mk_rec_fields :: [LHsRecField id arg] -> Bool -> HsRecFields id arg
mk_rec_fields fs False = HsRecFields { rec_flds = fs, rec_dotdot = Nothing }
diff --git a/compiler/rename/RnPat.hs b/compiler/rename/RnPat.hs
index 316bf34..9bd3718 100644
--- a/compiler/rename/RnPat.hs
+++ b/compiler/rename/RnPat.hs
@@ -566,17 +566,14 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot })
, hsRecPun = pun })) }
rn_dotdot :: Maybe Int -- See Note [DotDot fields] in HsPat
- -> Maybe Name -- The constructor (Nothing for an update
- -- or out of scope constructor)
+ -> Maybe Name -- The constructor (Nothing for an
+ -- out of scope constructor)
-> [LHsRecField Name (Located arg)] -- Explicit fields
-> RnM [LHsRecField Name (Located arg)] -- Filled in .. fields
rn_dotdot Nothing _mb_con _flds -- No ".." at all
= return []
- rn_dotdot (Just {}) Nothing _flds -- ".." on record update
- = do { case ctxt of
- HsRecFieldUpd -> addErr badDotDotUpd
- _ -> return ()
- ; return [] }
+ rn_dotdot (Just {}) Nothing _flds -- Constructor out of scope
+ = return []
rn_dotdot (Just n) (Just con) flds -- ".." on record construction / pat match
= ASSERT( n == length flds )
do { loc <- getSrcSpanM -- Rather approximate
@@ -723,9 +720,6 @@ badDotDotCon con
= vcat [ ptext (sLit "Illegal `..' notation for constructor") <+> quotes (ppr con)
, nest 2 (ptext (sLit "The constructor has no labelled fields")) ]
-badDotDotUpd :: SDoc
-badDotDotUpd = ptext (sLit "You cannot use `..' in a record update")
-
emptyUpdateErr :: SDoc
emptyUpdateErr = ptext (sLit "Empty record update")
More information about the ghc-commits
mailing list