Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : supercompiler

http://hackage.haskell.org/trac/ghc/changeset/3d9f524659b80633785eccb9126f5533f99bde8b

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

commit 3d9f524659b80633785eccb9126f5533f99bde8b
Author: Max Bolingbroke <batterseapo...@hotmail.com>
Date:   Tue Aug 2 19:47:57 2011 +0100

    Do not assume that the RHS of an unlifted Let is ok-for-speculation

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

 compiler/supercompile/Supercompile.hs             |    4 ++--
 compiler/supercompile/Supercompile/Core/Syntax.hs |    2 +-
 2 files changed, 3 insertions(+), 3 deletions(-)

diff --git a/compiler/supercompile/Supercompile.hs 
b/compiler/supercompile/Supercompile.hs
index 1621f60..f1dbc55 100644
--- a/compiler/supercompile/Supercompile.hs
+++ b/compiler/supercompile/Supercompile.hs
@@ -9,7 +9,7 @@ import qualified Supercompile.Drive.Process as S
 import BasicTypes (InlinePragma(..), InlineSpec(..), isActiveIn)
 import CoreSyn
 import CoreFVs    (exprFreeVars)
-import CoreUtils  (exprType)
+import CoreUtils  (exprType, bindNonRec)
 import CoreUnfold (exprIsConApp_maybe)
 import Coercion   (Coercion, isCoVar, isCoVarType, mkCoVarCo, mkAxInstCo)
 import DataCon    (DataCon, dataConWorkId, dataConAllTyVars, dataConRepArgTys, 
dataConTyCon, dataConName)
@@ -184,7 +184,7 @@ termToCoreExpr = term
         S.App e x           -> term e `App` Var x
         S.PrimOp pop tys es -> Var (mkPrimOpId pop) `mkTyApps` tys `mkApps` 
map term es
         S.Case e x ty alts  -> Case (term e) x ty (map alt alts)
-        S.Let x e1 e2       -> Let (NonRec x (term e1)) (term e2)
+        S.Let x e1 e2       -> bindNonRec x (term e1) (term e2)
         S.LetRec xes e      -> Let (Rec (map (second term) xes)) (term e)
         S.Cast e co         -> Cast (term e) co
     
diff --git a/compiler/supercompile/Supercompile/Core/Syntax.hs 
b/compiler/supercompile/Supercompile/Core/Syntax.hs
index 752c775..a1bd47f 100644
--- a/compiler/supercompile/Supercompile/Core/Syntax.hs
+++ b/compiler/supercompile/Supercompile/Core/Syntax.hs
@@ -74,7 +74,7 @@ data TermF ann = Var Id
                | App (ann (TermF ann)) Id
                | PrimOp PrimOp [Type] [ann (TermF ann)]
                | Case (ann (TermF ann)) Id Type [AltF ann]
-               | Let Id (ann (TermF ann)) (ann (TermF ann)) -- NB: might bind 
an unlifted thing, in which case the evaluation rules must change
+               | Let Id (ann (TermF ann)) (ann (TermF ann)) -- NB: might bind 
an unlifted thing, in which case evaluation changes. Unlike GHC, we do NOT 
assume the RHSes of unlifted bindings are ok-for-speculation.
                | LetRec [(Id, ann (TermF ann))] (ann (TermF ann))
                | Cast (ann (TermF ann)) Coercion
 



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to