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

On branch  : 

http://hackage.haskell.org/trac/ghc/changeset/854e2762143b2c2677a5a54e919524942dcd96a0

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

commit 854e2762143b2c2677a5a54e919524942dcd96a0
Author: Max Bolingbroke <batterseapo...@hotmail.com>
Date:   Tue Jan 31 17:27:54 2012 +0000

    Fix a bug where the talis of a generalised state would not be manifest

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

 compiler/supercompile/Supercompile/Drive/Split.hs |    3 +--
 1 files changed, 1 insertions(+), 2 deletions(-)

diff --git a/compiler/supercompile/Supercompile/Drive/Split.hs 
b/compiler/supercompile/Supercompile/Drive/Split.hs
index 8963c04..8606178 100644
--- a/compiler/supercompile/Supercompile/Drive/Split.hs
+++ b/compiler/supercompile/Supercompile/Drive/Split.hs
@@ -234,8 +234,7 @@ generalise gen (deeds, Heap h ids, k, qa) = do
     pprTrace "generalise: (gen_kfs, gen_xs')" (ppr (gen_kfs, gen_xs')) $ 
return ()
     
     let (ctxt_id, ctxt_ids) = takeUniqFromSupply splitterUniqSupply
-        (ctxt_ids0, ctxt_ids1) = splitUniqSupply ctxt_ids
-    return $ \opt -> generaliseSplit opt ctxt_ids0 (gen_kfs, gen_xs') deeds 
(Heap h ids, named_k, \ids -> (qaScruts qa, oneBracketed ctxt_ids1 (qaType qa) 
(Once ctxt_id, (Heap M.empty ids, [], annedQAToInAnnedTerm ids qa))))
+    return $ \opt -> generaliseSplit opt ctxt_ids (gen_kfs, gen_xs') deeds 
(Heap h ids, named_k, \ids -> (qaScruts qa, oneBracketed' (qaType qa) (Once 
ctxt_id, (emptyDeeds, Heap M.empty ids, [], annedQAToInAnnedTerm ids qa))))
 
 {-# INLINE generaliseSplit #-}
 generaliseSplit :: MonadStatics m



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

Reply via email to