OK, let's make it "Three Hoopl questions".

3) Consider this rewriting function:

cpRwMiddle dflags (CmmStore lhs rhs) _ = do
  u <- getUniqueUs
  let regSize      = cmmExprType dflags rhs
      newReg       = CmmLocal $ LocalReg u regSize
      newRegAssign = CmmAssign newReg rhs
      newMemAssign = CmmStore lhs (CmmReg newReg)
  return . Just . GUnit . BCons newRegAssign . BMiddle $ newMemAssign

Is this a correct way of generating new Uniques? If this function is evaluated 
twice will it generate two different uniques?

Janek

----- Oryginalna wiadomość -----
Od: "Jan Stolarek" <jan.stola...@p.lodz.pl>
Do: "ghc-devs" <ghc-devs@haskell.org>
Wysłane: piątek, 26 lipiec 2013 10:50:01
Temat: Two Hoopl questions

I have two questions about using Hoopl:

1) I'm debugging some Hoopl transformations that often fall into an infinite 
loop. Probably the easiest way to find the cause would be to allow only a 
limited number of iterations and then examining the rewritten output. I think 
that optimization fuel was designed exactly with this scenario in mind, but 
Compiler.Hoopl module in hoopl library does not re-export functions needed to 
use Fuel (e.g. runWithFuel). Why are these functions hidden? Is there another 
interface for using fuel?

2) In my algorithm I need to initialize all of the blocks in a graph with 
bottom element of a lattice, except for the entry block, which needs some other 
initial values. I've written something like this:

cmmCopyPropagation dflags graph = do
    let entry_blk = g_entry graph
    g' <- dataflowPassFwd graph [(entry_blk, (Top , Top))] $
            analRewFwd cpLattice cpTransfer cpRewrite
    return . fst $ g'

cpLattice = DataflowLattice "copy propagation" (Bottom, Bottom) cpJoin

However, it seems that Bottom values passed to cpLattice are ignored - I could 
replace them with `undefined` and the code would still run without causing an 
error. Is there something obviously wrong in the way I pass initial fact values 
to dataflowPassFwd, or should I look for the problem in other parts of my code?

Janek

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


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

Reply via email to