[commit: ghc] wip/T14152: Make Exitify CPP-free (168f8f3)
git at git.haskell.org
git at git.haskell.org
Wed Sep 6 14:19:13 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T14152
Link : http://ghc.haskell.org/trac/ghc/changeset/168f8f3d0f6c28efa23ad167a72e1f1d3e3b9706/ghc
>---------------------------------------------------------------
commit 168f8f3d0f6c28efa23ad167a72e1f1d3e3b9706
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Wed Sep 6 15:01:15 2017 +0100
Make Exitify CPP-free
>---------------------------------------------------------------
168f8f3d0f6c28efa23ad167a72e1f1d3e3b9706
compiler/simplCore/Exitify.hs | 7 -------
1 file changed, 7 deletions(-)
diff --git a/compiler/simplCore/Exitify.hs b/compiler/simplCore/Exitify.hs
index eb882e52..2079347 100644
--- a/compiler/simplCore/Exitify.hs
+++ b/compiler/simplCore/Exitify.hs
@@ -1,21 +1,15 @@
-{-# LANGUAGE CPP #-}
-
module Exitify ( exitifyProgram ) where
-#include "HsVersions.h"
-
import Var
import Id
import IdInfo
import CoreSyn
import CoreUtils
-import Util
import State
import Unique
import VarSet
import VarEnv
import CoreFVs
-import Outputable
import FastString
import Data.Bifunctor
@@ -64,7 +58,6 @@ exitifyProgram binds = map goTopLvl binds
-- join-points outside the joinrec.
exitify :: InScopeSet -> [(Var,CoreExpr)] -> (CoreExpr -> CoreExpr)
exitify in_scope pairs =
- ASSERT (all (isJoinId . fst) pairs)
\body ->mkExitLets exits (mkLetRec pairs' body)
where
mkExitLets ((exitId, exitRhs):exits') = mkLetNonRec exitId exitRhs . mkExitLets exits'
More information about the ghc-commits
mailing list