
Yes, all the inlining you expect should indeed happen. If it doesn't can you show us an example? Simon | -----Original Message----- | From: Manuel M. T. Chakravarty [mailto:chak@cse.unsw.edu.au] | Sent: 11 December 2000 13:41 | To: glasgow-haskell-users@haskell.org | Cc: keller@it.uts.edu.au | Subject: Transitive inlining | | | In the context of the array library, we stumbled over | another problem. Does GHC transitive inlining across | modules? Let's say, we have the following scenario: | | module B (foo) where | | {-# INLINE foo #-} | foo .. = ...bar... | | {-# INLINE bar #-} | bar .. = ... | | | module L (baz) where | | import B | | {#- INLINE baz #-} | baz .. = ...B.foo... | | | module Main where | | import L | | main .. = ...L.baz... | | GHC in this case inlines the whole expression "...B.foo..." | in `Main', but will it inline the right hand side of `B.bar' | in `Main' (or even of `B.foo')? If the INLINE pragma is | transitive across modules boundaries, one would hope so. | | It seems that GHC is not (always?) doing this inlining, | which already for a very simple benchmark costs us a factor | of 5 runtime! (With inlining - enforced by copying | definitions manually into `Main' - the code produced by GHC | is actually a little bit faster than the code for the | corresponding C program). | | Cheers, | Manuel | | PS: I had problems building GHCi and it seems as if my | message to cvs-ghc@haskell.org doesn't get through | somehow... | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users |

Simon Peyton-Jones
Yes, all the inlining you expect should indeed happen. If it doesn't can you show us an example?
Meanwhile, I think, the lack of inlining that I saw isn't connected to modules. Instead, the problem is that GHC thinks it knows more about my program than I do. More precisely, it seems to take an INLINE pragma just as an encouragement rather than a command to inline. In particular - at least if a function is large enough - it doesn't inline the function anymore if the function is used more than once.[1] This behaviour is a problem for our array library. We need very aggressive inlining. Would it maybe be possible to make -O2 interpret INLINE pragmas as obligatory? Cheers, Manuel [1] The function in question actually uses an INLINE 2 pragma - I guess that this doesn't matter.

"Manuel M. T. Chakravarty"
Meanwhile, I think, the lack of inlining that I saw isn't connected to modules. Instead, the problem is that GHC thinks it knows more about my program than I do. More precisely, it seems to take an INLINE pragma just as an encouragement rather than a command to inline. In particular - at least if a function is large enough - it doesn't inline the function anymore if the function is used more than once.[1]
Actually, the current behaviour - at least, as I understand it - in combination with modules leads IMHO to rather inconsistent behaviour. Given a module module M (foo) where {#- INLINE foo #-} foo = <biggish definition> GHC will not inline `foo' in module Main where import M bar = ...foo a... main = ...foo b...bar... However, it will inline foo twice in case of module N (bar) where import N bar = ...foo a... module Main where import M import N main = ...foo b...bar... although it is exactly the same code. In other words, using many modules leads to larger binaries and faster code. All this is understandable given that optimisation always included heuristics. However, for programmer supplied annotations, I think, it is problematic. Cheers, Manuel

"Manuel M. T. Chakravarty"
In particular - at least if a function is large enough - it doesn't inline the function anymore if the function is used more than once.
Moreover, I am wondering which the exact conditions are under which NOINLINE pragmas are ignored by the compiler. It seems at least always to be ignored in code like {-# NOINLINE foo #-} foo = <some code> bar .. = ..foo.. If that is the only occurence of `foo', inlining is certainly always save, but on the other hand if I take the trouble to add a NOINLINE pragma, I actually mean it. For example, I sometimes want to see what Core code is produced for <some code> using -ddump-simpl. The compiler can't know that, so IMHO it should better just follow my instructions, instead of trying to be extra smart. Cheers, Manuel
participants (2)
-
Manuel M. T. Chakravarty
-
Simon Peyton-Jones