[commit: ghc] wip/T11179: Expose cseExpr from CSE (122c655)
git at git.haskell.org
git at git.haskell.org
Sat Feb 4 14:14:24 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T11179
Link : http://ghc.haskell.org/trac/ghc/changeset/122c655927185131186814064f30a041cc361630/ghc
>---------------------------------------------------------------
commit 122c655927185131186814064f30a041cc361630
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Thu Feb 2 20:28:29 2017 -0500
Expose cseExpr from CSE
for the benefit of GHC API users who want to CSE single expressions.
>---------------------------------------------------------------
122c655927185131186814064f30a041cc361630
compiler/simplCore/CSE.hs | 5 ++++-
1 file changed, 4 insertions(+), 1 deletion(-)
diff --git a/compiler/simplCore/CSE.hs b/compiler/simplCore/CSE.hs
index 971b3e0..21dbd07 100644
--- a/compiler/simplCore/CSE.hs
+++ b/compiler/simplCore/CSE.hs
@@ -6,7 +6,7 @@
{-# LANGUAGE CPP #-}
-module CSE (cseProgram) where
+module CSE (cseProgram, cseOneExpr) where
#include "HsVersions.h"
@@ -373,6 +373,9 @@ tryForCSE toplevel env expr
-- top of the replaced sub-expression. This is probably not too
-- useful in practice, but upholds our semantics.
+cseOneExpr :: CoreExpr -> CoreExpr
+cseOneExpr = cseExpr emptyCSEnv
+
cseExpr :: CSEnv -> InExpr -> OutExpr
cseExpr env (Type t) = Type (substTy (csEnvSubst env) t)
cseExpr env (Coercion c) = Coercion (substCo (csEnvSubst env) c)
More information about the ghc-commits
mailing list