[GHC] #10595: BuiltinRules override other rules in some cases.

#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- It seems that the Class op * rules will override a user defined rule for class functions. This seems to be a long outstanding issue: http://stackoverflow.com/questions/9811294/rewrite-rules-not-firing-for- rules-matching-multiple-instance-methods I also just ran into someone else on the haskell IRC channel who had an even simpler example then the one on that page: {{{#!hs {-# NOINLINE d #-} {-# RULES "d exp" d exp = exp #-} d :: (Double -> Double) -> (Double -> Double) d f = f . (+20.0) g :: Double -> Double g = (+5.0) main = do print $ d exp 1.0 -- FAIL should print 2.718281828459045 >> printed exp 21.0 instead print $ d g 3.0 -- PASS should print 28.0 -- Compiled with: -- ghc -fenable-rewrite-rules -O rules.hs }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gjsimms): Well, I don't really know how to use trac to modify files... Anyway the ruleTest.hs file is a working version (rule gets hit) of example in the description. ruleTest2.hs is a failing case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by NicX): Seconding gjsimms comment re. rulesTest.hs. That version uses exp' (defined on lines 6-7) instead of exp so the comment on line 13 should say: -- PASS should print 2.718281828459045 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by gjsimms): * version: 7.10.1 => 7.11 Comment: Tested this occurs in HEAD on my machine. I think I have determined why this occurs, I don't see an easy fix offhand. If this is an know issue or if it is not a priority feel free to change the priority/close. Evaluation of rewrite rules seems to work up the syntax tree (lower leafs will be rewritten before the final expressions). So given a BuiltinRule for exp (exp -> exp???) and the Rule (f . exp -> exp) for some fixed f. Processing 1) f . exp 2) (.) f exp Rewrite branches, f has no rule. 3) (.) f exp??? Done, no more rewrites possible. Some code which I believe demonstrates this correctly. (compile with rewrite rules active) {{{ class A a where ida :: a -> a idb :: a -> a class B a where idB :: a -> a instance A Bool where ida _ = False idb _ = True instance B Bool where idB False = True idB True = False {-# NOINLINE ida' #-} ida' :: A a => a -> a ida' = ida {-# NOINLINE idb' #-} idb' :: A a => a -> a idb' = idb {-# RULES "SuccessB" forall f. idB (idB f) = idB f "Failure1" forall f. ida (ida f) = idb f "Failure2" forall f. ida' (ida f) = idb f "Success1" forall f. ida (ida' f) = idb f "Success2" forall f. ida' (ida' f) = idb' f #-} main = do print (ida (ida True)) -- FAIL should print True >> prints False print (ida' (ida True)) -- FAIL should print True >> prints False print (ida' (ida' True)) -- PASS should print True print (ida (ida' True)) -- PASS should print TRUE print (idB (idB False)) -- PASS should print True (INLINING may make this run specific it seems consistent on my machine though) }}} I would appreciate someone more knowledgeable than me checking this out... I have tried forcing BuiltinRules activation on the last step only -- infinite loop in the rewriter during tests (fixes the issue for simple cases). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): GHC has a crude-but-effective way to control the order of application of rules, called "phases". See the reference to phase control in [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/rewrite- rules.html 7.23.1 in the manual]. Phases count down; currently 2, 1, 0. Currently, though, a class-method has a built-in rule (selection from dictionary) which is always active. There is no way for the user to override this, to make it active in (say) phase 1 and later. If you could, that would solve your problem. The only straightforward solution I can see is to make the built-in rule for class methods inactive in phase 2, so that user-written rules take precedence. The trouble with this is that it will delay the moment at which the per-instance functions (which may have rules of their own) become visible. Rather than attempt a change with global consequences, I suggest that you simply make a new intermediate function, just as you have done with `ida'`. Instead of NOINLINE you can say `INLINE [1]` which will inline it in phase 1. Now write your rules for `ida'`. This has the effect of delaying the built-in class-method rule for `ida` without affecting any other functions. I'll add a paragraph to the user manual about this. And I'll close this as wont-fix, because there is a good workaround and no obviously better design. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): In this case it seems that what we want to do is rewrite the left hand side of the new rule itself. Not sure if this is a good idea in general though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

In this case it seems that what we want to do is rewrite the left hand side of the new rule itself. Not sure if this is a good idea in general
#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Replying to [comment:5 rwbarton]: though. That sounds delicate and I have no idea what will really happen. The solution I proposed is simple and robust. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gjsimms): I am happy with the workaround/documentation at this point: Just to note, this can be done almost entirely in the Rule system by substituting into temporary functions. So class-methods can be used normally with rewrite rules. {{{ {-# INLINE [1] f' #-} f' = f {-# RULES f = f' #-} {-# RULES (exp1 (f' ...) ...) = exp2) #-} }}} Long term I think it would be most clear if BuiltinRules had no effect on user supplied rewrite rules. This does affect some current libraries e.g. all the RULES in Control.Arrow do nothing, I do not know if/how it affects other libraries. Feel free to close. I do think it is worthwhile making note of in case the simplifier gets overhauled at any point in the future. ida' idb' above can be inlined in the above (all phases) and the rule will still fire for me, I figure this may be somewhat random. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Replying to [comment:5 rwbarton]:
In this case it seems that what we want to do is rewrite the left hand side of the new rule itself. Not sure if this is a good idea in general
#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Replying to [comment:6 simonpj]: though.
That sounds delicate and I have no idea what will really happen. The
solution I proposed is simple and robust. Agreed, but when the method in question belongs to a type class defined in another package (as in the original report), this solution is non-modular. A second library that defines `d'` cannot define a rule for `d' exp` that coexists with a rule for `d exp` unless the two libraries agree on a "`exp'`". It would be nicer if the rules could somehow refer directly to the- instance-of-exp-for-Double. Of course, this is in feature request territory. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10595: BuiltinRules override other rules in some cases.
-------------------------------------+-------------------------------------
Reporter: gjsimms | Owner:
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: closed Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10595: BuiltinRules override other rules in some cases.
-------------------------------------+-------------------------------------
Reporter: gjsimms | Owner:
Type: bug | Status: closed
Priority: high | Milestone:
Component: Compiler | Version: 7.11
Resolution: invalid | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: closed => new * resolution: invalid => Comment: HEAD now shows the following warning for the example from the description: {{{ Test.hs:4:11: warning: Rule "d exp" may never fire because rule "Class op exp" for ‘exp’ might fire first Probable fix: add phase [n] or [~n] to the competing rule }}} That "Probable fix" is not probable at all, because "Class op exp" is a built-in rule. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Yes; I don't know what the right design is here, so currently I'm doing nothing. See also #10528. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): In [changeset:"a1dd7dd6ea276832aef0caaf805f0ab9f4e16262/ghc" a1dd7dd/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a1dd7dd6ea276832aef0caaf805f0ab9f4e16262" Fallout from more assiduous RULE warnings GHC now warns if rules compete, so that it's not predicatable which will work and which will not. E.g. {-# RULES f (g x) = ... g True = ... #-} If we had (f (g True)) it's not clear which rule would fire. This showed up fraility in the libraries. * Suppress warnigns in Control.Arrow, Control.Category for class methods. At the moment we simply don't have a good way to write a RULE with a class method in the LHS. See Trac #1595. Arrow and Category attempt to do so; I have silenced the complaints with -fno-warn-inline-rule-shadowing, but it's not a great solution. * Adjust the NOINLINE pragma on 'GHC.Base.map' to account for the map/coerce rule * Adjust the rewrite rules in Enum, especially for the "literal 1" case. See Note [Enum Integer rules for literal 1]. * Suppress warnings for 'bytestring' e.g. libraries/bytestring/Data/ByteString.hs:895:1: warning: Rule "ByteString specialise break (x==)" may never fire because rule "Class op ==" for ‘==’ might fire first Probable fix: add phase [n] or [~n] to the competing rule }}} The commit message should have said #10595! Typo. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * cc: bgamari (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10595#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC