[GHC] #10699: Regression: panic with custom rewrite rules on primops

GHC ghc-devs at haskell.org
Tue Jul 28 16:28:54 UTC 2015


#10699: Regression: panic with custom rewrite rules on primops
-------------------------------------+-------------------------------------
              Reporter:  thomie      |             Owner:
                  Type:  bug         |            Status:  new
              Priority:  normal      |         Milestone:
             Component:  Compiler    |           Version:  7.10.2-rc2
              Keywords:              |  Operating System:  Unknown/Multiple
          Architecture:              |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
             Test Case:              |        Blocked By:
              Blocking:              |   Related Tickets:  #10555
Differential Revisions:              |
-------------------------------------+-------------------------------------
 The following program results in a panic with ghc-7.10.2 (and also HEAD
 with the patches for #10528 and #10595 applied), but not with ghc-7.10.1.

 {{{#!haskell
 {-# LANGUAGE MagicHash #-}
 module T10555b where

 import GHC.Prim

 {-# RULES
 "double commute left *" forall x1 x2 x3. (*##) x1 ((*##) x2 x3)
     = (*##) ((*##) x2 x3) x1
   #-}

 {-# RULES
 "double **4" forall x . x **## 4.0##
     = let xx = x *## x in xx *## xx
   #-}
 }}}

 {{{
 $ ghc-7.10.2 -fforce-recomp -O T10555b.hs
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.10.2 for x86_64-unknown-linux):
         Simplifier ticks exhausted
   When trying RuleFired double commute left *
   To increase the limit, use -fsimpl-tick-factor=N (default 100)
   If you need to do this, let GHC HQ know, and what factor you needed
   To see detailed counts use -ddump-simpl-stats
   Total ticks: 4004
 }}}

 I find this suprising, because there isn't anything to rewrite yet, is
 there?

 These are the prerequisites to trigger the bug:
   * both rules are needed
   * the function (`*##`) should be a primop

 If I replace the function (`*##`) by `f` below, I don't get a panic, but I
 do get the following warning:
 {{{
     RULE left-hand side too complicated to desugar
       Optimised lhs: case f x2 x3 of wild_00 { __DEFAULT ->
                      f x1 wild_00
                      }
       Orig lhs: case f x2 x3 of wild_00 { __DEFAULT -> f x1 wild_00 }
 }}}

 {{{#!haskell
 {-# NOINLINE f #-}
 f :: Double# -> Double# -> Double#
 f = undefined
 }}}
 Note that the first rewrite rule (`"double commute left *"`) is buggy by
 itself, since it will loop on `times4` (with any compiler version):

 {{{#!haskell
 times4 :: Double -> Double
 times4 (D# x) = D# ((x *## x) *## (x *## x))
 }}}

 So I'm not quite sure if there is a actually a bug in GHC here, but I
 don't understand what's going on either.

 These examples are extracted from the [https://hackage.haskell.org/package
 /fast-math fast-math] package.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10699>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list