[commit: ghc] wip/T12626: Replace foldl App by mkApps everywhere (3e3d964)
git at git.haskell.org
git at git.haskell.org
Thu Sep 29 17:22:22 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T12626
Link : http://ghc.haskell.org/trac/ghc/changeset/3e3d9644365a7f9e614b97a957b8fdfc6d6c877a/ghc
>---------------------------------------------------------------
commit 3e3d9644365a7f9e614b97a957b8fdfc6d6c877a
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Thu Sep 29 13:16:01 2016 -0400
Replace foldl App by mkApps everywhere
>---------------------------------------------------------------
3e3d9644365a7f9e614b97a957b8fdfc6d6c877a
compiler/coreSyn/CoreArity.hs | 2 +-
compiler/coreSyn/CoreSubst.hs | 2 +-
compiler/deSugar/DsMeta.hs | 2 +-
compiler/simplCore/SetLevels.hs | 4 ++--
4 files changed, 5 insertions(+), 5 deletions(-)
diff --git a/compiler/coreSyn/CoreArity.hs b/compiler/coreSyn/CoreArity.hs
index f5e7673..1ab50b4 100644
--- a/compiler/coreSyn/CoreArity.hs
+++ b/compiler/coreSyn/CoreArity.hs
@@ -888,7 +888,7 @@ etaExpand n orig_expr
-- See Note [Eta expansion and source notes]
(expr', args) = collectArgs expr
(ticks, expr'') = stripTicksTop tickishFloatable expr'
- sexpr = foldl App expr'' args
+ sexpr = mkApps expr'' args
retick expr = foldr mkTick expr ticks
-- Wrapper Unwrapper
diff --git a/compiler/coreSyn/CoreSubst.hs b/compiler/coreSyn/CoreSubst.hs
index ffd8c2a..81af530 100644
--- a/compiler/coreSyn/CoreSubst.hs
+++ b/compiler/coreSyn/CoreSubst.hs
@@ -1008,7 +1008,7 @@ simple_app subst (Tick t e) as
| t `tickishScopesLike` SoftScope
= mkTick t $ simple_app subst e as
simple_app subst e as
- = foldl App (simple_opt_expr subst e) as
+ = mkApps (simple_opt_expr subst e) as
----------------------
simple_opt_bind,simple_opt_bind' :: Subst -> CoreBind -> (Subst, Maybe CoreBind)
diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs
index 9395d35..7756b8d 100644
--- a/compiler/deSugar/DsMeta.hs
+++ b/compiler/deSugar/DsMeta.hs
@@ -1774,7 +1774,7 @@ unC (MkC x) = x
rep2 :: Name -> [ CoreExpr ] -> DsM (Core a)
rep2 n xs = do { id <- dsLookupGlobalId n
- ; return (MkC (foldl App (Var id) xs)) }
+ ; return (MkC (mkApps (Var id) xs)) }
dataCon' :: Name -> [CoreExpr] -> DsM (Core a)
dataCon' n args = do { id <- dsLookupDataCon n
diff --git a/compiler/simplCore/SetLevels.hs b/compiler/simplCore/SetLevels.hs
index c28be3a..9c37434 100644
--- a/compiler/simplCore/SetLevels.hs
+++ b/compiler/simplCore/SetLevels.hs
@@ -316,7 +316,7 @@ lvlExpr env expr@(_, AnnApp _ _) = do
let (lapp, rargs) = left (n_val_args - arity) expr []
rargs' <- mapM (lvlMFE False env) rargs
lapp' <- lvlMFE False env lapp
- return (foldl App lapp' rargs')
+ return (mkApps lapp' rargs')
where
n_val_args = count (isValArg . deAnnotate) args
arity = idArity f
@@ -335,7 +335,7 @@ lvlExpr env expr@(_, AnnApp _ _) = do
_otherwise -> do
args' <- mapM (lvlMFE False env) args
fun' <- lvlExpr env fun
- return (foldl App fun' args')
+ return (mkApps fun' args')
-- We don't split adjacent lambdas. That is, given
-- \x y -> (x+1,y)
More information about the ghc-commits
mailing list