[GHC] #15569: Constant folding optimises 1 into 3

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- A recent Hadrian issue [1] led me to finding a rather embarrassing bug: {{{#!hs {-# NOINLINE sub #-} -- This is just subtraction in disguise minus :: Int -> Int -> Int minus x y = (8 - y) - (8 - x) {-# NOINLINE minus #-} main :: IO () main = print (2 `minus` 1) }}} When compiled using `ghc-8.6.0.20180810` without optimisation this prints `1`, as expected, but when compiled with `-O` this prints `3`. Here is the incorrect rewrite rule [2]: {{{#!hs (L y :-: v) :-: (L x :-: w) -> return $ mkL (y-x) `add` (w `add` v) }}} This should be changed to: {{{#!hs (L y :-: v) :-: (L x :-: w) -> return $ mkL (y-x) `add` (w `sub` v) }}} Happy to submit the fix, but I'm not yet fully convinced that there are no other lurking bugs. This whole constant folding business is very error- prone. [1] https://github.com/snowleopard/hadrian/issues/641 [2] https://github.com/ghc/ghc/blob/master/compiler/prelude/PrelRules.hs#L1786 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by snowleopard): * related: => #9136 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by snowleopard: Old description:
A recent Hadrian issue [1] led me to finding a rather embarrassing bug:
{{{#!hs {-# NOINLINE sub #-} -- This is just subtraction in disguise minus :: Int -> Int -> Int minus x y = (8 - y) - (8 - x) {-# NOINLINE minus #-}
main :: IO () main = print (2 `minus` 1) }}}
When compiled using `ghc-8.6.0.20180810` without optimisation this prints `1`, as expected, but when compiled with `-O` this prints `3`.
Here is the incorrect rewrite rule [2]:
{{{#!hs (L y :-: v) :-: (L x :-: w) -> return $ mkL (y-x) `add` (w `add` v) }}}
This should be changed to:
{{{#!hs (L y :-: v) :-: (L x :-: w) -> return $ mkL (y-x) `add` (w `sub` v) }}}
Happy to submit the fix, but I'm not yet fully convinced that there are no other lurking bugs. This whole constant folding business is very error-prone.
[1] https://github.com/snowleopard/hadrian/issues/641
[2] https://github.com/ghc/ghc/blob/master/compiler/prelude/PrelRules.hs#L1786
New description: A recent Hadrian issue [1] led me to finding a rather embarrassing bug: {{{#!hs -- This is just subtraction in disguise minus :: Int -> Int -> Int minus x y = (8 - y) - (8 - x) {-# NOINLINE minus #-} main :: IO () main = print (2 `minus` 1) }}} When compiled using `ghc-8.6.0.20180810` without optimisation this prints `1`, as expected, but when compiled with `-O` this prints `3`. Here is the incorrect rewrite rule [2]: {{{#!hs (L y :-: v) :-: (L x :-: w) -> return $ mkL (y-x) `add` (w `add` v) }}} This should be changed to: {{{#!hs (L y :-: v) :-: (L x :-: w) -> return $ mkL (y-x) `add` (w `sub` v) }}} Happy to submit the fix, but I'm not yet fully convinced that there are no other lurking bugs. This whole constant folding business is very error- prone. [1] https://github.com/snowleopard/hadrian/issues/641 [2] https://github.com/ghc/ghc/blob/master/compiler/prelude/PrelRules.hs#L1786 -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * priority: normal => highest -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by snowleopard): Here is a quick fix: https://phabricator.haskell.org/D5109. Adding the above example as a single test and closing this ticket seems a bit unsatisfactory. I think we need to either 1) do some automated correctness checking or 2) refactor the code so that it's more obvious that there are no remaining bugs. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: hsyl20 (added) Comment: Yes, I think we are going to need to revert Phab:D2858 for now. The fact that this snuck through CI until now is deeply concerning and I'm also far from convinced that there aren't more bugs lurking. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hsyl20): Ouch, my bad :/ I triple checked those rules but it wasn't enough. Some automated correctness checking would be good indeed... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: alpmestan (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by snowleopard): In an attempt to find a safer implementation for constant folding I came up with this: https://gist.github.com/snowleopard/2dd93951cfd42e03aa04a4aa696ca029 This may be an overkill, but does shift most of the verification load to the compiler: we still need to manually verify a few key functions like `eval`, but the constant folding rules can't be written incorrectly. NB: I covered most of the rules, but not all. Also I haven't really shown what to do with negative variables (non-literals) in the end, but this bit doesn't look too complicated. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3
-------------------------------------+-------------------------------------
Reporter: snowleopard | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.6.1
Component: Compiler | Version: 8.6.1-beta1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #9136 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Krzysztof Gogolewski

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ChaiTRex): * differential: => Phab:D5109 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ChaiTRex): * Attachment "ConstantFolding.hs" added. Constant folding tester program -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ChaiTRex): * Attachment "ThisGHC.hs" added. Constant folding tester program TH helper -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ChaiTRex): = Semi-exhaustive testing is being performed using GHC before the fix = Using the attached program, I'm doing semi-exhaustive testing of constant folding up to an expression nesting depth of two (up to something like `(a + b)*(c + d)`) with literal and variable values in `[0, 1, 3, 7] :: [Int]`. Note that the attached program takes the better part of a day, so it might not be prudent to add it to the test suite unless that can be significantly reduced or a "very, very slow" testing option can be added. == Testing is being done before fix == To ensure the tester actually detects problems, the tester program was performed until it detected this bug report's bug with GHC before the fix (at GHC commit `ff29fc84c03c800cfa04c2a00eb8edf6fa5f4183`). The tester program is still running and full output will be attached when the program finishes. The first few lines of output are: {{{ ERROR! ((0 - x0) - (0 - x1)) is optimized incorrectly! ERROR! ((0 - x0) - (1 - x0)) is optimized incorrectly! ERROR! ((0 - x0) - (1 - x1)) is optimized incorrectly! ERROR! ((0 - x0) - (3 - x0)) is optimized incorrectly! ⋮ ⋮ ⋮ ⋮ ⋮ ⋮ ⋮ ⋮ ⋮ ⋮ ⋮ ⋮ ⋮ ⋮ ⋮ ⋮ }}} == Testing will be done after fix == Testing will next be performed using GHC at `HEAD` (after the above fix). Results will be posted in my next comment in about a day. == The program == There are two modules attached: * `ThisGHC.hs`: a Template Haskell helper module for running the specific GHC installation a program was compiled with. * `ConstantFolding.hs`: a program that repeatedly compiles a certain number of expressions at a time (to avoid heap overflows from compiling all expressions at once) with `-O2` and tests their output against those expressions compiled with `-O0`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Sounds great -- looking forward to the results! Thanks for doing this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I think we'll be releasing 8.6.1 with the constant folding patch so we should run ChaiTRex's test program at least once before releasing. ChaiTRex, you said you'll be posting results, do you have the results yet? I'll also try to run it on my system. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ChaiTRex): * Attachment "BadResultsBeforePatch.txt" added. Bad results before patch -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ChaiTRex): Apologies for the delay: I had no power for a while and had to restart. The results before the patch are attached and point out only this bug. The results after the patch point out no bugs: {{{ }}} So, `Int`s look good on my end, at least up to an expression nesting depth of two (''i.e.'', up to something like `(a + b)*(c + d)`). For any future needs, I've put a newly-multithreaded version of the tester on GitHub at [https://github.com/ChaiTRex/ConstantFoldingTest ChaiTRex/ConstantFoldingTest]. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Comment (by snowleopard): Great job, ChaiTRex! This gives us some confidence. Could you, perhaps, generate a representative subset of all your tests that will be small enough to be added to the testsuite? For example, without iterating over different constants, yet still hitting each constant folding rule? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): For the record, here's ~~a paper~~ [https://arxiv.org/pdf/1809.02161.pdf a report] about how these kind of optimisations should be specified in a declarative language (like snowleopard's attempt above). Ultimately, these declarations could be synthesised by an SMT solver out of a language semantics (a.k.a. algebraic structure, in our case). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Comment (by snowleopard): Thanks @sgraf! I think we can proceed with the testing-based solution for now, but I hope we will revisit constant folding rules in future and reimplement them in a more type-safe way. I can volunteer to do that once most of the urgent work on Hadrian is complete. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ChaiTRex): I've started reworking my code to generate a small subset of test cases that use one specific fixed constant (100^th^ prime, 200^th^ prime, ''etc''. to avoid coincidentally passing tests) for each spot where a literal or variable is expected, which should cut down significantly on the number of tests. I'd like to further cut down on the number of tests while still getting full coverage, but I've only skimmed some of the constant folding rules. Am I right in assuming that the following are true? * `Int`s are the only type we need to test (if this isn't true, my reworking will make the code take a type parameter, so generating tests for additional types will be simple). * The following expression shapes are the only ones required, where `∘` is multiplication, addition, or subtraction and where multiple occurrences in one expression can represent different operations. '''Note:''' negation stops after single-`∘` expressions: * `a` * `-a` * `a ∘ b` * `a ∘ -b` * `-a ∘ b` * `a ∘ (b ∘ c)` * `(a ∘ b) ∘ c` * `(a ∘ b) ∘ (c ∘ d)` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Comment (by flip101): Since the phrases "SMT solver" and "compiler-checked way" came up. Wouldn't it be good for GHC to move into the direction that CakeML has chosen and then (at least for some parts) verify the compiler with proof? It could be a good addition to CI and also for local builds to run after the test suite. Excuse me if the question is too broad of scope, but the ticket seems a good example for it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): I picked all rules from D2858, including the wrong and the correct version of `(L y :-: v) :-: (L x :-: w)` and used sympy to compute the difference between LHS and RHS symbolically. Result: all differences simplify to 0, except that one rule that was found to be wrong. Code: https://gist.github.com/monoidal/3d5565b986a013639389fc57081d2781 All of the rules use addition, subtraction and multiplication only (matters would be different if there was division). This makes me confident that the rules are algebraically correct. It doesn't mean the code is completely correct, but any remaining errors will be of different nature. If someone is willing to do further review, I would suggest things like: double-checking the code surrounding the rules, checking if integer overflow can occur, does this apply only to Int/Integer or other types etc. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Comment (by jean): @sgraf, I'm interested in the SMT direction. I'm currently looking for a project for my SMT course, and this sounds interesting. Can you point to more resources? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): @jean, I'm not particularly invested in the field, but on page 6 in the report I linked there is a table of superoptimizers (I confused these with supercompilation in the past, which is totally different), the respective papers of which might be a good start. In particular, everything doing "synthesis" is probably fueled by an SMT solver. I think the essence boils down to formalising source and target language (which should be same algebraic structure in our example) and let the SMT solver synthesize a RHS to a given LHS expression which has minimal cost wrt. some metric. This seems like the most recent approach: https://arxiv.org/pdf/1711.04422.pdf -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15569: Constant folding optimises 1 into 3 -------------------------------------+------------------------------------- Reporter: snowleopard | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9136 | Differential Rev(s): Phab:D5109 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => closed * resolution: => fixed Comment: The fix was merged to both master and 8.6, so closing. I think the testing effort should be tracked in its own ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15569#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC