
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

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"

Yes it'll generate two uniques. I think that's fine.
Simon
| -----Original Message-----
| From: ghc-devs [mailto:ghc-devs-bounces@haskell.org] On Behalf Of Jan Stolarek
| Sent: 26 July 2013 16:56
| To: ghc-devs
| Subject: Re: Two Hoopl questions
|
| 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"

Hello Jan, Re (1), there is an important invariant that your transformations should uphold to avoid infinite loops. This invariant is described in the Hoopl paper:
• The lattice must have no infinite ascending chains; that is, every sequence of calls to fact_join must eventually return NoChange. • The transfer function must be monotonic: given a more infor- mative fact in, it must produce a more informative fact out. • The rewrite function must be sound: if it replaces a node n by a replacement graph g, then g must be observationally equivalent to n under the assumptions expressed by the incoming dataflow fact f. Moreover, analysis of g must produce output fact(s) that are at least as informative as the fact(s) produced by applying the transfer function to n. For example, if the transfer function says that x=7 after the node n, then after analysis of g, x had better still be 7. • A transformation that uses deep rewriting must not return a re- placement graph which contains a node that could be rewritten indefinitely.
These are all local invariants, so you should go through all of your data structures and functions and check if they fulfill the invariants. Re optimization fuel, I do not really recommend using it to debug infinite loops (since what you will need to do is repeatedly run with different values of fuel and manually look at what kind of "infinite behavior" is going on. We used to have a flag -dopt-fuel (http://blog.ezyang.com/2011/06/debugging-compilers-with-optimization-fuel/) which did this, but I guess it got removed at some point. I haven't looked at your other questions closely yet. Cheers, Edward

Thank you Edward. I am aware of these requirements - my problem is writing the code in which these will always hold (I'm optimizing Cmm and hand-written Cmm files tend to cause many problems that don't appear in automatically generated Cmm). Having a debugging tool in form of Fuel would be helpful for me, because instead of getting a freeze and seeing no output from -ddump-cmm I would see incorrectly transformed Cmm that would allow me to track bugs more easily.
• The transfer function must be monotonic: given a more infor- mative fact in, it must produce a more informative fact out. I spent some considerable time thinking about this. Consider a simple example of copy propagation. Let's assume that { x = NAC }, i.e. we know that x has been defined earlier but is Not-A-Constant and so we cannot rewrite it. Now we have something llike this:
x := 3; y := x; Here we are allowed to rewrite y := x with y := 3, because after first statement we learn that { x = 3 }. Now consider this: x := 3; x := very_unsafe_stg_call(); y := x; Here, after the first statement we learn that { x = 3 }, but after the second one we learn once again that x is NAC and so we are not allowed to rewrite statement y := x. So the value of x can change from NAC to a constant and from constant to a NAC. Is such a transfer function monotonic? Janek

Thank you Edward. I am aware of these requirements - my problem is writing the code in which these will always hold (I'm optimizing Cmm and hand-written Cmm files tend to cause many problems that don't appear in automatically generated Cmm). Having a debugging tool in form of Fuel would be helpful for me, because instead of getting a freeze and seeing no output from -ddump-cmm I would see incorrectly transformed Cmm that would allow me to track bugs more easily.
In that case, I would recommend taking a look at when -dopt-fuel got removed and seeing if you can put it back in. I quite liked this feature and it is too bad it is gone.
• The transfer function must be monotonic: given a more infor- mative fact in, it must produce a more informative fact out.
I spent some considerable time thinking about this. Consider a simple example of copy propagation. Let's assume that { x = NAC }, i.e. we know that x has been defined earlier but is Not-A-Constant and so we cannot rewrite it. Now we have something llike this:
x := 3; y := x;
Here we are allowed to rewrite y := x with y := 3, because after first statement we learn that { x = 3 }. Now consider this:
x := 3; x := very_unsafe_stg_call(); y := x;
Here, after the first statement we learn that { x = 3 }, but after the second one we learn once again that x is NAC and so we are not allowed to rewrite statement y := x. So the value of x can change from NAC to a constant and from constant to a NAC. Is such a transfer function monotonic?
This is a point of confusion; I got confused about this when I was working on Hoopl. What is meant by a transfer function over instruction i is monotonic is: if x <= y then f_i(x) <= f_i(y) It says nothing about the "change" in x as you move along the statements. Thus, for your example, very_unsafe_stg_call always puts x to be NAC; this is trivially monotonic since NAC <= NAC. Edward

On 26/07/13 22:56, Edward Z. Yang wrote:
Thank you Edward. I am aware of these requirements - my problem is writing the code in which these will always hold (I'm optimizing Cmm and hand-written Cmm files tend to cause many problems that don't appear in automatically generated Cmm). Having a debugging tool in form of Fuel would be helpful for me, because instead of getting a freeze and seeing no output from -ddump-cmm I would see incorrectly transformed Cmm that would allow me to track bugs more easily.
In that case, I would recommend taking a look at when -dopt-fuel got removed and seeing if you can put it back in. I quite liked this feature and it is too bad it is gone.
Guilty. I got rid of the fuel (in GHC's version of the dataflow algorithm). I think removing it was worth a percent or two in compile-time performance - not a lot, but this was one of a whole heap of such things that I did to get the new codegen from about 100% to 5% overhead. I've no objection to the idea of optimisation fuel, but it should be an optional thing that doesn't cost anything if you don't use it. Cheers, Simon

It's easy to get confused, but in fact the bedrock issues are quite simple. As Edward says, a function f is monotonic iff x <= y implies f(x) <= f(y) Monotonicity does NOT mean that x <= f(x)!!! The transfer function, and the 'join' function, must all be monotonic. It's that simple. ======= I would *not* mess with the rewrite fuel. It's not used at all for analysis, only for rewrites, and it's the analysis that is going bad on you. Instead, simply arrange give an extra "fuel" counter to function 'loop' line 603 of Compiler.Hoopl.Dataflow. If you run out of fuel, print some information about blocks left in the to-do list and the next few iterations. You can give enough fuel for (say) 100 passes through each block. Do this if DEBUG is defined. In this way you'll get much more information than non-termination. ========== For the constant-prop stuff, you want to know what each fact means. Something like x -> BOT "I have no information about x" x -> val "x always has value val, on all the control flow paths I have seen so far" x -> NAC "x can have more than one value depending on the control flow path that reaches this point" Now the transfer functions in your email make perfect sense. Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces@haskell.org] On Behalf Of Jan Stolarek | Sent: 26 July 2013 22:48 | To: Edward Z. Yang | Cc: ghc-devs | Subject: Re: Two Hoopl questions | | Thank you Edward. I am aware of these requirements - my problem is writing the | code in which these | will always hold (I'm optimizing Cmm and hand-written Cmm files tend to cause | many problems that | don't appear in automatically generated Cmm). Having a debugging tool in form of | Fuel would be | helpful for me, because instead of getting a freeze and seeing no output from - | ddump-cmm I would | see incorrectly transformed Cmm that would allow me to track bugs more easily. | | > > • The transfer function must be monotonic: given a more infor- | > > mative fact in, it must produce a more informative fact out. | I spent some considerable time thinking about this. Consider a simple example of | copy propagation. | Let's assume that { x = NAC }, i.e. we know that x has been defined earlier but is | Not-A-Constant | and so we cannot rewrite it. Now we have something llike this: | | x := 3; | y := x; | | Here we are allowed to rewrite y := x with y := 3, because after first statement we | learn that { x | = 3 }. Now consider this: | | x := 3; | x := very_unsafe_stg_call(); | y := x; | | Here, after the first statement we learn that { x = 3 }, but after the second one | we learn once | again that x is NAC and so we are not allowed to rewrite statement y := x. So the | value of x can | change from NAC to a constant and from constant to a NAC. Is such a transfer | function monotonic? | | Janek | | _______________________________________________ | ghc-devs mailing list | ghc-devs@haskell.org | http://www.haskell.org/mailman/listinfo/ghc-devs

I'll allow myself to ask my second question again: 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 second parameter to DataflowLattice 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

What happens when you put a loop in your code? Edward Excerpts from Jan Stolarek's message of Tue Jul 30 08:34:44 -0700 2013:
I'll allow myself to ask my second question again:
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 second parameter to DataflowLattice 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

For some reason they are ignored, or at least the rewritten code looks as if only a single pass was done. I have facts represented like this:
data AssignmentFactBot a = Bottom
| Const (M.Map a CmmExpr)
I initialize the entry node with:
g' <- dataflowPassFwd graph [(entry_blk, Const M.empty)] $
analRewFwd cpLattice cpTransfer (cpRewrite dflags)
And lattice is initialized with Bottom. Now the join function:
joinCpFacts old Bottom = panic "AAAAAAAAAAA"
joinCpFacts (Const old) (Const new) = ...
joinCpFacts Bottom Bottom = panic "Joining bottom with bottom"
joinCpFacts Bottom (Const _) = panic "Joining bottom with const"
Two last panics are intended - they should never happen. The first one is for debugging purposes and surprisingly it is never called - only the second equation is. I'm puzzled. Where did I go wrong?
Janek
----- Oryginalna wiadomość -----
Od: "Edward Z. Yang"
I'll allow myself to ask my second question again:
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 second parameter to DataflowLattice 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

OK, I think I didn't give enough explanation in my last mail. My understanding is that entry block of the graph will be initialized with a fact (Const M.empty), while every other node will be initialized with Bottom. Now, when I reach a block that is first block in a loop it will have more than one predecessor (let's assume that it has two). One predecessor will have fact (Const ...) propagated from the entry node, but the other one will not be analyzed yet and therefore should be Bottom. That's why I think it should be picked up by first equation of joinCpFacts. Later on, when we reach end of a loop we will propagate (Const ...) to the entry block of a loop and only then we will be joining two (Const ...) facts - that's when second equation of joinCpFacts should come in to play.
Janek
----- Oryginalna wiadomość -----
Od: "Jan Stolarek"
I'll allow myself to ask my second question again:
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 second parameter to DataflowLattice 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

Does Hoopl handle Bottom internally? By "Bottom" I mean the loop-breaking thing that means "this predecessor does not execute". From the debugging output I added to my code it looks that it in fact does because it doesn't do a join when first analyzing a block with two predecessors. If this is really the case then what is the purpose of defining bottom in DataflowLattice?
Janek
----- Oryginalna wiadomość -----
Od: "Edward Z. Yang"
I'll allow myself to ask my second question again:
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 second parameter to DataflowLattice 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

By the laws of lattices, A joined with bottom is A. So Hoopl skips actually doing it, IIRC. It's pretty hard to tell what is going on here. Edward Excerpts from Jan Stolarek's message of Wed Jul 31 09:44:46 -0700 2013:
Does Hoopl handle Bottom internally? By "Bottom" I mean the loop-breaking thing that means "this predecessor does not execute". From the debugging output I added to my code it looks that it in fact does because it doesn't do a join when first analyzing a block with two predecessors. If this is really the case then what is the purpose of defining bottom in DataflowLattice?
Janek
----- Oryginalna wiadomość ----- Od: "Edward Z. Yang"
Do: "Jan Stolarek" DW: "Simon Peyton-Jones" , "ghc-devs" Wysłane: wtorek, 30 lipiec 2013 20:40:53 Temat: Re: Two Hoopl questions What happens when you put a loop in your code?
Edward
Excerpts from Jan Stolarek's message of Tue Jul 30 08:34:44 -0700 2013:
I'll allow myself to ask my second question again:
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 second parameter to DataflowLattice 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

| Does Hoopl handle Bottom internally? By "Bottom" I mean the loop-breaking thing
| that means "this predecessor does not execute". From the debugging output I
I don't think so. You supply a lattice
data DataflowLattice a = DataflowLattice
{ fact_name :: String -- Documentation
, fact_bot :: a -- Lattice bottom element
, fact_join :: JoinFun a -- Lattice join plus change flag
-- (changes iff result > old fact)
}
and the fact_bot value should really be the bottom element.
Simon
| -----Original Message-----
| From: Jan Stolarek [mailto:jan.stolarek@p.lodz.pl]
| Sent: 31 July 2013 17:45
| To: Edward Z. Yang
| Cc: Simon Peyton-Jones; ghc-devs
| Subject: Re: Two Hoopl questions
|
| Does Hoopl handle Bottom internally? By "Bottom" I mean the loop-breaking thing
| that means "this predecessor does not execute". From the debugging output I
| added to my code it looks that it in fact does because it doesn't do a join when
| first analyzing a block with two predecessors. If this is really the case then what is
| the purpose of defining bottom in DataflowLattice?
|
| Janek
|
| ----- Oryginalna wiadomość -----
| Od: "Edward Z. Yang"
participants (4)
-
Edward Z. Yang
-
Jan Stolarek
-
Simon Marlow
-
Simon Peyton-Jones