[commit: ghc] wip/T12618: Always use ConApp in CoreSyn (32b4719)

git at git.haskell.org git at git.haskell.org
Thu Oct 6 23:20:34 UTC 2016


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

On branch  : wip/T12618
Link       : http://ghc.haskell.org/trac/ghc/changeset/32b47198c2f6b365611e144b0730c9dff12ba206/ghc

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

commit 32b47198c2f6b365611e144b0730c9dff12ba206
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Tue Oct 4 15:46:59 2016 -0400

    Always use ConApp in CoreSyn


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

32b47198c2f6b365611e144b0730c9dff12ba206
 compiler/coreSyn/CoreSyn.hs | 10 +++++-----
 1 file changed, 5 insertions(+), 5 deletions(-)

diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs
index fdb9578..b519bdf 100644
--- a/compiler/coreSyn/CoreSyn.hs
+++ b/compiler/coreSyn/CoreSyn.hs
@@ -1193,7 +1193,7 @@ maybeUnfoldingTemplate :: Unfolding -> Maybe CoreExpr
 maybeUnfoldingTemplate (CoreUnfolding { uf_tmpl = expr })
   = Just expr
 maybeUnfoldingTemplate (DFunUnfolding { df_bndrs = bndrs, df_con = con, df_args = args })
-  = Just (mkLams bndrs (mkApps (Var (dataConWorkId con)) args))
+  = Just (mkLams bndrs (ConApp con args))
 maybeUnfoldingTemplate _
   = Nothing
 
@@ -1481,7 +1481,9 @@ mkConApp      :: DataCon -> [Arg b] -> Expr b
 mkApps    f args = foldl App                       f args
 mkCoApps  f args = foldl (\ e a -> App e (Coercion a)) f args
 mkVarApps f vars = foldl (\ e a -> App e (varToCoreExpr a)) f vars
-mkConApp con args = mkApps (Var (dataConWorkId con)) args
+mkConApp con args =
+    WARN ( dataConRepFullArity con /= length args, text "mkConApp: artiy mismatch" $$ ppr con )
+    ConApp con args
 
 mkTyApps  f args = foldl (\ e a -> App e (typeOrCoercion a)) f args
   where
@@ -1490,9 +1492,7 @@ mkTyApps  f args = foldl (\ e a -> App e (typeOrCoercion a)) f args
       | otherwise                        = Type ty
 
 mkConApp2 :: DataCon -> [Type] -> [Var] -> Expr b
-mkConApp2 con tys arg_ids = Var (dataConWorkId con)
-                            `mkApps` map Type tys
-                            `mkApps` map varToCoreExpr arg_ids
+mkConApp2 con tys arg_ids = mkConApp con (map Type tys ++ map varToCoreExpr arg_ids)
 
 
 -- | Create a machine integer literal expression of type @Int#@ from an @Integer at .



More information about the ghc-commits mailing list