[GHC] #14092: hs-boot unfolding visibility not consistent between --make and -c

#14092: hs-boot unfolding visibility not consistent between --make and -c -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Keywords: hs-boot. | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- duog's comment in https://phabricator.haskell.org/D3815#107812 pointed out an inconsistency between hs-boot handling in --make and -c that I have been dimly aware of for some time now. Here is how to trigger the situation: {{{ -- A.hs-boot module A where f :: Int -> Int -- B.hs module B where import {-# SOURCE #-} A -- A.hs module A where import B f :: Int -> Int f x = x + 1 -- C.hs module C where import {-# SOURCE #-} A g = f 2 }}} When we run `ghc-head C.hs --make -O -ddump-simpl -fforce-recomp`, we see that f has been successfully inlined: {{{ -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} g :: Int [GblId, Caf=NoCafRefs, Str=m, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] g = GHC.Types.I# 3# }}} However, if we then one-shot compile C.hs, as in `ghc-head -c C.hs -O -ddump-simpl -fforce-recomp`, the unfolding is not seen: {{{ -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} C.g1 :: Int [GblId, Caf=NoCafRefs, Str=m, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] C.g1 = GHC.Types.I# 2# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} g :: Int [GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=False, WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 20 0}] g = f C.g1 }}} The crux of the matter is that `--make` and `-c` have different rules about when to make use of the unfolded definition. The `--make` rule is: compile the modules in some topological order. Any module that comes after `A.hs` sees the improved unfoldings. And as it turns out, the current topological order GHC picks is this: {{{ [1 of 4] Compiling A[boot] ( A.hs-boot, A.o-boot ) [2 of 4] Compiling B ( B.hs, B.o ) [3 of 4] Compiling A ( A.hs, A.o ) [4 of 4] Compiling C ( C.hs, C.o ) }}} The `-c` rule is more complicated. Every module records a list of transitive module dependencies, and whether or not a boot or non-boot was used. We load an hi-boot file if NONE of the modules we imported "saw" the full hi module, AND we only did direct SOURCE imports. If anyone has transitively imported A.hs, we load the hi file. In the example above, C.hs ONLY imports A.hs-boot, so hs-boot is obliged to load A.hi-boot, and thus it does not see the unfolding. The `-c` behavior is the correct behavior, because with the `--make` behavior it is easy to get into a situation where the build is dependent on the topological order chosen. Consider: * `A.hs-boot` * `B.hs-boot` * `A.hs` imports `A.hs-boot`, `B.hs-boot` * `B.hs` imports `A.hs-boot`, `B.hs-boot` (Ignore the fact that in GHC today you can't actually directly import your hs-boot file; you can fix this by importing dummy modules.) Now you can see that depending on the order you compile, e.g., A.hs-boot, B.hs-boot, A.hs, B.hs versus B.hs, A.hs, either A.hs or B.hs will be compiled with the unfoldings for its partner, but not vice versa. This doesn't sound good! Unfortunately, fixing things properly in `--make` mode is quite troublesome. To understand why, we have to first remind ourself about loop retypechecking in make mode. Remember that GHC knot-ties all of the typechecker data structures together (https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/TyingTheKnot). This means that at the point we typecheck an hs-boot file, we are building an (immutable) graph on top of the impoverished, type signature only declarations from the hs-boot file. When we finish typechecking the loop closer, the only way to "update" all of the old references to the hs-boot file is to throw out the entire graph and rebuild it from scratch (the loop retypecheck!) So let's think about the A.hs-boot B.hs A.hs C.hs case. At the point we're typechecking A.hs, we throw out the graph referencing A.hs-boot and rebuild it referencing A.hs so that everything gets knot-tied to A.hs. But THEN, C.hs comes around, and it's like, "Oy, I don't want the A.hs version of the graph, I want the A.hs-boot version of the graph." In `-c` mode, this is not a problem, since we have to rebuild the graph from scratch anyway, but in `--make` this is a big deal, since we have to throw everything out and rebuild it AGAIN. One implementation strategy that doesn't involve mucking about with HPT retypechecking is to somehow make the typechecker aware of what unfoldings it should "see" and which it should not. The idea is that if it can ignore unfoldings that it doesn't have legitimate access to, that should be "just as good" as having typechecked against the hs-boot graph itself. But this sounds very tricky and difficult to get right... so here we are. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14092 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14092: hs-boot unfolding visibility not consistent between --make and -c -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * keywords: hs-boot. => hs-boot Comment: Thanks for this explanation ezyang, this is a very tricky area and I think I'm finally starting to understand what's going on. Note that your first example can be modified to exhibit another bug: to A.hs add {{{ h = f }}} to C.hs change to {{{ g = h 2 }}} This compiles in --make mode, even though C should not be able to see h! You say that -c behaviour is correct, and in the sense that it is predictable and deterministic, of course you are right. However, the current --make behaviour produces code that is at least as good(modulo the bug exhibited above), and in your first (A.hs-boot, B.hs, A.hs, C.hs) example, it is better! I wonder if it is possible to exploit laziness to always have unfoldings available even when importing an .hs-boot. trac:13299 seems relevant. I am currently working on an idea to split parsing, typechecking, simplifying, and codegen for the purpose of allowing more parallelism in --make mode. (I have a mostly-working patch, which I hope to have on phab this week, although it will be a little untidy). This might allow having unfoldings available from .hs-boot imports. Regarding "views" into the home package table, I think this may be a fruitful idea. It seems to me to offer nice solutions to this ticket, as well as trac:9370. :pieinthesky: I have thought of storing in interface files, instead of an unfolding, loosely a "map" of (way, OptimizationSettings)->unfolding. This would require the notion of views into the home package table. I think this would help address problems such as trac:10923. It would also allow eliminating the idea of "way" interfaces (.dyn_hi, .p_hi, etc), with all of that information in a single .hi file. I do admit that I'm not sure exactly what benefit removing way interfaces would provide, except that it does seem cleaner to me. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14092#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14092: hs-boot unfolding visibility not consistent between --make and -c -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
One implementation strategy that doesn't involve mucking about with HPT retypechecking is to somehow make the typechecker aware of what unfoldings it should "see" and which it should not.
This is reminiscent of #9370 (see comment 20 and following). I don't know how tight the linkage is. BTW did your really mean "make the typechecker aware"? It's the simplifier that is doing more inlining than it should, isn't it? (Not the typechecker.) And how much does all this matter anyway? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14092#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14092: hs-boot unfolding visibility not consistent between --make and -c -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * priority: normal => low Comment:
However, the current --make behaviour produces code that is at least as good(modulo the bug exhibited above), and in your first (A.hs-boot, B.hs, A.hs, C.hs) example, it is better! I wonder if it is possible to exploit laziness to always have unfoldings available even when importing an .hs- boot.
Yes. But the price you pay is that the compilation of A and B can no longer be done in parallel. I tend to think of an hs-boot files as one way you could speed up compilation, a bit like header files, at the cost of the quality of optimized code.
It's the simplifier that is doing more inlining than it should, isn't it? (Not the typechecker.)
Yes!
And how much does all this matter anyway?
Not much, probably! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14092#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Yes. But the price you pay is that the compilation of A and B can no longer be done in parallel. I tend to think of an hs-boot files as one way you could speed up compilation, a bit like header files, at the cost of
#14092: hs-boot unfolding visibility not consistent between --make and -c -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by duog): Replying to [comment:3 ezyang]: the quality of optimized code.
I find this very convincing. Do you think this is a controversial view?
It's the simplifier that is doing more inlining than it should, isn't it? (Not the typechecker.)
Yes!
The typechecker is providing the Ids with too many unfoldings attached though, right? Also see the example in comment 1 where a program typechecks because it can see a name that should be hidden to it.
And how much does all this matter anyway?
Not much, probably!
This is of interest to me because I am working on --make mode (trac:14095, trac:14103), and the treatment of hs-boot modules is by far the trickiest part. It seems that the correct behaviour isn't very well specified. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14092#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14092: hs-boot unfolding visibility not consistent between --make and -c -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang):
I find this very convincing. Do you think this is a controversial view?
The typechecker is providing the Ids with too many unfoldings attached
Not controversial per se, but most people who use hs-boot files only do so because they must use it to break an import loop. So it's not really a common way to use hs-boot files. though, right? Technically, unfolding attachment happens during interface loading (called "typechecking the interface", but no real "typechecking" really takes place.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14092#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14092: hs-boot unfolding visibility not consistent between --make and -c -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
I tend to think of an hs-boot files as one way you could speed up compilation
FWIW I have never thought of hs-boot files that way. Just as a 9not terribly satisfactory) way to break module loops. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14092#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC