[GHC] #8832: Constant-folding regression wrt `clearBit (bit 0) 0 `

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` ------------------------------+-------------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.8.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime performance bug Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | ------------------------------+-------------------------------------------- While implementing `zeroBits` (see [83bd2f5fc7e/base]) I noticed that constant folding of the expression `clearBit (bit 0) 0` regressed (and improved at the same time) from GHC 7.6.3 to GHC 7.8.1, specifically, the following module {{{#!haskell {-# LANGUAGE CPP #-} module M where import Data.Bits import Data.Int import Data.Word #define T(s,T) \ s :: T ; \ s = clearBit (bit 0) 0 ; \ T(i,Int) T(i8,Int8) T(i16,Int16) T(i32,Int32) T(i64,Int64) T(w,Word) T(w8,Word8) T(w16,Word16) T(w32,Word32) T(w64,Word64) T(z,Integer) }}} compiled with GHC 7.8.1RC2 results in the following Core output: {{{#!haskell -- GHC 7.8.1RC2 i = I# (andI# 1 (notI# 1)) i8 = I8# 0 i16 = I16# 0 i32 = I32# 0 i64 = I64# 0 w = W# (__word 0) w8 = W8# (__word 0) w16 = W16# (__word 0) w32 = W32# (__word 0) w64 = W64# (__word 0) z2 = $w$cbit 0 z1 = complementInteger z2 z = andInteger z2 z1 }}} Thus, `i` and `z` are not properly constant-folded in GHC 7.8.1RC2. With GHC 7.6.3, however, `i` and `z` were properly folded to `0`: {{{#!haskell -- GHC 7.6.3 i = I# 0 i8 = case $fBitsInt8_$cbit i of _ { I8# x#_aDf -> case $fBitsInt8_$cbit i of _ { I8# x#1_aDr -> I8# (word2Int# (and# (int2Word# x#_aDf) (xor# (int2Word# x#1_aDr) (__word 18446744073709551615)))) } } i16,i32,i64 -- equivalent to i8 w = W# (__word 0) w8 = case $fBitsWord8_$cbit i of _ { W8# x#_aEV -> case $fBitsWord8_$cbit i of _ { W8# x#1_aF5 -> W8# (and# x#_aEV (xor# x#1_aF5 (__word 255))) } } w16,w32,w64 -- equivalent to w8 z = __integer 0 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` --------------------------------------------+------------------------------ Reporter: hvr | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Changes (by simonpj): * cc: jstolarek (added) Comment: Jan might you look at this? It seems to be in the general area you were working in. Yell if you can't. Thanks! Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` --------------------------------------------+------------------------------ Reporter: hvr | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by jstolarek): Sorry Simon, but I don't have enough time to look into this one. I'm working on #8707 at the moment. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` --------------------------------------------+------------------------------ Reporter: hvr | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Changes (by simonpj): * owner: => simonpj Comment: I have a fix for this, but only on my laptop. And since I can't build on my laptop (we have a seg-fault on Windows that needs someone to pay attention to) it'll have to wait till I'm back in the office. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 `
--------------------------------------------+------------------------------
Reporter: hvr | Owner: simonpj
Type: bug | Status: new
Priority: normal | Milestone: 7.8.1
Component: Compiler | Version: 7.8.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime performance bug | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
--------------------------------------------+------------------------------
Comment (by Simon Peyton Jones

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 `
--------------------------------------------+------------------------------
Reporter: hvr | Owner: simonpj
Type: bug | Status: new
Priority: normal | Milestone: 7.8.1
Component: Compiler | Version: 7.8.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime performance bug | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
--------------------------------------------+------------------------------
Comment (by Simon Peyton Jones

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 `
--------------------------------------------+------------------------------
Reporter: hvr | Owner: simonpj
Type: bug | Status: new
Priority: normal | Milestone: 7.8.1
Component: Compiler | Version: 7.8.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime performance bug | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
--------------------------------------------+------------------------------
Comment (by Simon Peyton Jones

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` --------------------------------------------+------------------------------ Reporter: hvr | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by simonpj): I believe I've fixed this. I'm not sure if it's worth merging into 7.8; the status quo is definitely not a show-stopper. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------------------+------------------------- Reporter: hvr | Owner: Type: bug | simonpj Priority: normal | Status: new Component: Compiler | Milestone: 7.8.1 Resolution: | Version: Operating System: Unknown/Multiple | 7.8.1-rc2 Type of failure: Runtime performance bug | Keywords: Test Case: | Architecture: simplCore/should_compile/T8832 | Unknown/Multiple Blocking: | Difficulty: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by simonpj): * testcase: => simplCore/should_compile/T8832 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------------------+------------------------- Reporter: hvr | Owner: Type: bug | simonpj Priority: normal | Status: Component: Compiler | closed Resolution: fixed | Milestone: Operating System: Unknown/Multiple | Version: Type of failure: Runtime performance bug | 7.8.1-rc2 Test Case: | Keywords: simplCore/should_compile/T8832 | Architecture: Blocking: | Unknown/Multiple | Difficulty: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by thoughtpolice): * status: new => closed * resolution: => fixed * milestone: 7.8.1 => Comment: Thanks Simon. I don't think this is worth merging with the fix Herbert put in the 7.8 branch, so I'm punting it off the 7.8.1 milestone now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------------------+------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: Runtime performance bug | Architecture: Test Case: | Unknown/Multiple simplCore/should_compile/T8832 | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by simonpj): * owner: simonpj => * status: closed => new * resolution: fixed => Comment: The test fails on 32-bit machines, because we don't have 64-bit primops on a 32-bit machine, so the constant folding doesn't work. Maybe we should have 64-bit primops on a 32-bit machine, but that's a separate story. Meanwhile, we need to fix the test so that it omits the 64-bit test on 32-bit machines. Austin can you do this, post release? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------------------+------------------------- Reporter: hvr | Owner: Type: bug | thoughtpolice Priority: normal | Status: new Component: Compiler | Milestone: Resolution: | Version: Operating System: Unknown/Multiple | 7.8.1-rc2 Type of failure: Runtime performance bug | Keywords: Test Case: | Architecture: simplCore/should_compile/T8832 | Unknown/Multiple Blocking: | Difficulty: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by simonpj): * owner: => thoughtpolice -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 `
-------------------------------------------------+-------------------------
Reporter: hvr | Owner:
Type: bug | thoughtpolice
Priority: normal | Status: new
Component: Compiler | Milestone:
Resolution: | Version:
Operating System: Unknown/Multiple | 7.8.1-rc2
Type of failure: Runtime performance bug | Keywords:
Test Case: | Architecture:
simplCore/should_compile/T8832 | Unknown/Multiple
Blocking: | Difficulty:
| Unknown
| Blocked By:
| Related Tickets:
-------------------------------------------------+-------------------------
Comment (by Herbert Valerio Riedel

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------------------+------------------------- Reporter: hvr | Owner: Type: bug | thoughtpolice Priority: normal | Status: new Component: Compiler | Milestone: Resolution: | 7.10.1 Operating System: Unknown/Multiple | Version: Type of failure: Runtime performance bug | 7.8.1-rc2 Test Case: | Keywords: simplCore/should_compile/T8832 | Architecture: Blocking: | Unknown/Multiple | Difficulty: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by thoughtpolice): * milestone: => 7.10.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------+------------------------------------- Reporter: hvr | Owner: thoughtpolice Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.8.1-rc2 Resolution: | Keywords: Differential Revisions: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime Unknown/Multiple | performance bug Difficulty: Unknown | Test Case: Blocked By: | simplCore/should_compile/T8832 Related Tickets: | Blocking: -------------------------------------+------------------------------------- Changes (by simonpj): * priority: normal => high Comment: The bug is fixed. The only issue is that the test has some 64-bit stuff in it, and on a 32-bit machine that doesn't constant-fold. Which is probably fine. To close the ticket we just need to make the test depend on whether we are on a 64-bit machine. I don't know how to do that, but it can't be hard. Could someone do it? I'll make it "high" priority to get it some attention, rather than because it's terribly important. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 `
-------------------------------------+-------------------------------------
Reporter: hvr | Owner: thoughtpolice
Type: bug | Status: new
Priority: high | Milestone: 7.10.1
Component: Compiler | Version: 7.8.1-rc2
Resolution: | Keywords:
Operating System: | Architecture: Unknown/Multiple
Unknown/Multiple | Difficulty: Unknown
Type of failure: Runtime | Blocked By:
performance bug | Related Tickets:
Test Case: |
simplCore/should_compile/T8832 |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by Reid Barton

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------+------------------------------------- Reporter: hvr | Owner: thoughtpolice Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Runtime | Blocked By: performance bug | Related Tickets: Test Case: | simplCore/should_compile/T8832 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by rwbarton): Is this what you had in mind, Simon? Without the `#ifdef`s the grep output on a 32-bit system would contain uniques, so I couldn't just add a `.stdout-ws-32` file. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------+------------------------------------- Reporter: hvr | Owner: thoughtpolice Type: bug | Status: closed Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.8.1-rc2 Resolution: fixed | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Runtime | Blocked By: performance bug | Related Tickets: Test Case: | simplCore/should_compile/T8832 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: That's great thank you. (Do you know about `-dsuppress-uniques`? But in any case, it's probably best to suppress the 64-bit test on a 32-bit system.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 `
-------------------------------------+-------------------------------------
Reporter: hvr | Owner: thoughtpolice
Type: bug | Status: closed
Priority: high | Milestone: 7.10.1
Component: Compiler | Version: 7.8.1-rc2
Resolution: fixed | Keywords:
Operating System: | Architecture: Unknown/Multiple
Unknown/Multiple | Difficulty: Unknown
Type of failure: Runtime | Blocked By:
performance bug | Related Tickets:
Test Case: |
simplCore/should_compile/T8832 |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by hvr):
Replying to [comment:15 Reid Barton
In [changeset:"a72614c40186521da7ba090b102436e61a80b7a7/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="a72614c40186521da7ba090b102436e61a80b7a7" Make T8832 operative on 32-bit systems (#8832)
(Also, the 'extra_clean' was unnecessary.) }}}
Btw, now that I saw that commit, I've seen other testcases making use of the pre-defined `SIZEOF_HSWORD` (and there's also `WORD_SIZE_IN_BITS`) CPP symbol to test for wordsize. Would that have worked as well? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Btw, now that I saw that commit, I've seen other testcases making use of
#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------+------------------------------------- Reporter: hvr | Owner: thoughtpolice Type: bug | Status: closed Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.8.1-rc2 Resolution: fixed | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Runtime | Blocked By: performance bug | Related Tickets: Test Case: | simplCore/should_compile/T8832 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by rwbarton): Replying to [comment:18 hvr]: the pre-defined `SIZEOF_HSWORD` (and there's also `WORD_SIZE_IN_BITS`) CPP symbol to test for wordsize. Would that have worked as well? Predefined by what? I tried `ghc -E -optP-dM -cpp foo.hs; cat foo.hspp` as suggested somewhere in the User's Guide to see what C preprocessor symbols were automatically defined and there wasn't anything like that among them. Or do you mean `#include`ing one of GHC's header files? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | simplCore/should_compile/T8832 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * owner: thoughtpolice => * status: closed => new * resolution: fixed => Comment: `z` is still not properly constant-folded. The test is deceiving. It greps for '#', and there is no '#' in the output for `z` (not until #8274 is implemented, which I'm working on). {{{ $ ghc-7.10.0.20150123 Temp.hs -ddump-simpl -fforce-recomp -dsuppress-all -O [1 of 1] Compiling M ( Temp.hs, Temp.o ) ==================== Tidy Core ==================== Result size of Tidy Core = {terms: 10, types: 3, coercions: 0} z2 z2 = bitInteger 0 z1 z1 = complementInteger z2 z z = andInteger z2 z1 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 `
-------------------------------------+-------------------------------------
Reporter: hvr | Owner:
Type: bug | Status: new
Priority: high | Milestone: 7.12.1
Component: Compiler | Version: 7.8.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | simplCore/should_compile/T8832
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Thomas Miedema

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | simplCore/should_compile/T8832 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): The problem here is that the `Bits` instance for `Integer` overrides `bit`, using it's own `bitInteger` function in place of the usual `bitDefault`. `bitDefault` is constant folded by `PrelRules` by virtue of being implemented in terms of `shiftL`. This is presumably done to optimize the case of construction of a `BigNat` for large arguments, but `bitBigNat#`, which is what handles this case, is currently just the naive implementation with a TODO. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------+------------------------------------- Reporter: hvr | Owner: ekmett Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Core Libraries | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | simplCore/should_compile/T8832 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * cc: ekmett (added) * owner: => ekmett * component: Compiler => Core Libraries Comment: OK so this is a library problem, not a GHC problem. Core Libraries Committee, might you take this on? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------+------------------------------------- Reporter: hvr | Owner: ekmett Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Core Libraries | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | simplCore/should_compile/T8832 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): For the record, hvr has indicated that he will eventually be implementing a more efficient `bitInteger`. However, this still means that `Integer` won't get proper constant folding (as it won't be implemented in terms of `shiftL`). I'm not really sure it's fair to call this a library problem: the compiler currently makes the library author choose between having a constant-folded `bit` implementation (by implementing in terms of other operations which are constant folded) or an implementation which is implemented efficiently for the type in question. There are a few ways we could handle this: 1. add a `PrelRule` to specifically handle `Bits.bits` 2. somehow extend the rule rewriting system to allow these rules to be expressed in the source language Option 1 is unfortunate in that `Bits.bits` is likely far from the last operation which will need this treatment. Moreover, it leaves users who want to implement other types implementing `Bits` and similar classes covered by `PrelRules` high and dry. Arguably this is a limitation of the rule rewriting system, hence option 2. At first glance it would seem like allowing a rule to match conditioned on the nature of its arguments (either literal or non-literal) and allowing compile-time evaluation of the RHS may be sufficient to address this. This, however, would be non-trivial to implement (namely compile- time evaluation would require the interpreter) and may present termination issues. For these reasons (and perhaps others I haven't yet thought of) I doubt this is a viable path. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------+------------------------------------- Reporter: hvr | Owner: ekmett Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Core Libraries | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | simplCore/should_compile/T8832 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ekmett): Simon, I can talk to Herbert about fixing up `bitBigNat#`, but if the issue is that having it at all kills constant folding, it sounds like we'd still have a problem. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------+------------------------------------- Reporter: hvr | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Core Libraries | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | simplCore/should_compile/T8832 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * owner: ekmett => bgamari Comment: I discussed this with Simon during out GHC meeting and we agreed that the best solution here would be to add a `PrelRule` covering `bit`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------+------------------------------------- Reporter: hvr | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Core Libraries | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | simplCore/should_compile/T8832 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by jstolarek): * cc: jstolarek (removed) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------+------------------------------------- Reporter: hvr | Owner: bgamari Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Core Libraries | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | simplCore/should_compile/T8832 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1255 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D1255 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 `
-------------------------------------+-------------------------------------
Reporter: hvr | Owner: bgamari
Type: bug | Status: patch
Priority: high | Milestone: 8.0.1
Component: Core Libraries | Version: 7.8.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Runtime | Test Case:
performance bug | simplCore/should_compile/T8832
Blocked By: | Blocking:
Related Tickets: | Differential Revisions: Phab:D1255
-------------------------------------+-------------------------------------
Comment (by Austin Seipp

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 `
-------------------------------------+-------------------------------------
Reporter: hvr | Owner: bgamari
Type: bug | Status: patch
Priority: high | Milestone: 8.0.1
Component: Core Libraries | Version: 7.8.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Runtime | Test Case:
performance bug | simplCore/should_compile/T8832
Blocked By: | Blocking:
Related Tickets: | Differential Revisions: Phab:D1255
-------------------------------------+-------------------------------------
Comment (by Thomas Miedema

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` -------------------------------------+------------------------------------- Reporter: hvr | Owner: bgamari Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Core Libraries | Version: 7.8.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | simplCore/should_compile/T8832 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1255 -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8832: Constant-folding regression wrt `clearBit (bit 0) 0 `
-------------------------------------+-------------------------------------
Reporter: hvr | Owner: bgamari
Type: bug | Status: closed
Priority: high | Milestone: 8.0.1
Component: Core Libraries | Version: 7.8.1-rc2
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Runtime | Test Case:
performance bug | simplCore/should_compile/T8832
Blocked By: | Blocking:
Related Tickets: | Differential Revisions: Phab:D1255
-------------------------------------+-------------------------------------
Comment (by Thomas Miedema
participants (1)
-
GHC