[commit: ghc] master: Replace [PostTc id Type] with PostTc id [Type] (c738b12)
git at git.haskell.org
git at git.haskell.org
Sun Sep 20 10:42:02 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/c738b1231bc63a45be87d49cc42b7644681e509d/ghc
>---------------------------------------------------------------
commit c738b1231bc63a45be87d49cc42b7644681e509d
Author: Matthew Pickering <matthewtpickering at gmail.com>
Date: Sun Sep 20 12:18:21 2015 +0200
Replace [PostTc id Type] with PostTc id [Type]
This gives a clearer indication as to what gets filled in
when. It was suggested by Richard on D1152.
Test Plan: ./validate
Reviewers: austin, goldfire, bgamari
Reviewed By: goldfire, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1245
>---------------------------------------------------------------
c738b1231bc63a45be87d49cc42b7644681e509d
compiler/hsSyn/Convert.hs | 4 +++-
compiler/hsSyn/HsExpr.hs | 11 ++++++-----
compiler/hsSyn/PlaceHolder.hs | 3 +++
compiler/parser/RdrHsSyn.hs | 3 ++-
compiler/rename/RnExpr.hs | 2 +-
5 files changed, 15 insertions(+), 8 deletions(-)
diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs
index 9466ab0..0d4eaea 100644
--- a/compiler/hsSyn/Convert.hs
+++ b/compiler/hsSyn/Convert.hs
@@ -712,7 +712,9 @@ cvtl e = wrapL (cvt e)
; return $ RecordCon c' noPostTcExpr (HsRecFields flds' Nothing)}
cvt (RecUpdE e flds) = do { e' <- cvtl e
; flds' <- mapM cvtFld flds
- ; return $ RecordUpd e' (HsRecFields flds' Nothing) [] [] [] }
+ ; return $ RecordUpd e'
+ (HsRecFields flds' Nothing)
+ PlaceHolder PlaceHolder PlaceHolder }
cvt (StaticE e) = fmap HsStatic $ cvtl e
{- Note [Dropping constructors]
diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs
index a3c1f6c..63fea7a 100644
--- a/compiler/hsSyn/HsExpr.hs
+++ b/compiler/hsSyn/HsExpr.hs
@@ -293,11 +293,12 @@ data HsExpr id
(HsRecordBinds id)
-- (HsMatchGroup Id) -- Filled in by the type checker to be
-- -- a match that does the job
- [DataCon] -- Filled in by the type checker to the
- -- _non-empty_ list of DataCons that have
- -- all the upd'd fields
- [PostTc id Type] -- Argument types of *input* record type
- [PostTc id Type] -- and *output* record type
+ (PostTc id [DataCon])
+ -- Filled in by the type checker to the
+ -- _non-empty_ list of DataCons that have
+ -- all the upd'd fields
+ (PostTc id [Type]) -- Argument types of *input* record type
+ (PostTc id [Type]) -- and *output* record type
-- For a type family, the arg types are of the *instance* tycon,
-- not the family tycon
diff --git a/compiler/hsSyn/PlaceHolder.hs b/compiler/hsSyn/PlaceHolder.hs
index 91d37ea..19f2bd4 100644
--- a/compiler/hsSyn/PlaceHolder.hs
+++ b/compiler/hsSyn/PlaceHolder.hs
@@ -12,6 +12,7 @@ import NameSet
import RdrName
import Var
import Coercion
+import DataCon (DataCon)
import Data.Data hiding ( Fixity )
import BasicTypes (Fixity)
@@ -102,4 +103,6 @@ type DataId id =
, Data (PostTc id Type)
, Data (PostTc id Coercion)
+ , Data (PostTc id [Type])
+ , Data (PostTc id [DataCon])
)
diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs
index beb3b3b..a83f6b3 100644
--- a/compiler/parser/RdrHsSyn.hs
+++ b/compiler/parser/RdrHsSyn.hs
@@ -1178,7 +1178,8 @@ 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 (mk_rec_fields fs dd) [] [] [])
+ = return (RecordUpd exp (mk_rec_fields fs dd)
+ PlaceHolder PlaceHolder PlaceHolder)
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/RnExpr.hs b/compiler/rename/RnExpr.hs
index aaac8f1..d4b5e72 100644
--- a/compiler/rename/RnExpr.hs
+++ b/compiler/rename/RnExpr.hs
@@ -258,7 +258,7 @@ rnExpr (RecordCon con_id _ rbinds)
rnExpr (RecordUpd expr rbinds _ _ _)
= do { (expr', fvExpr) <- rnLExpr expr
; (rbinds', fvRbinds) <- rnHsRecBinds HsRecFieldUpd rbinds
- ; return (RecordUpd expr' rbinds' [] [] [],
+ ; return (RecordUpd expr' rbinds' PlaceHolder PlaceHolder PlaceHolder,
fvExpr `plusFV` fvRbinds) }
rnExpr (ExprWithTySig expr pty PlaceHolder)
More information about the ghc-commits
mailing list