[GHC] #13209: ghc panic with optimization.

GHC ghc-devs at haskell.org
Mon Jan 30 11:23:13 UTC 2017


#13209: ghc panic with optimization.
-------------------------------------+-------------------------------------
           Reporter:  1chb           |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  7.10.3
           Keywords:                 |  Operating System:  Linux
       Architecture:  x86            |   Type of failure:  GHC rejects
                                     |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 ghc eqFn && ./eqFn

 Works fine and the program runs fine too, but a bit slow.

 Adding optimization (-O) makes ghc panic (even after setting a bigger
 'tick' factor):

 ghc -fsimpl-tick-factor=2000 -O eqFn && ./eqFn
 [1 of 1] Compiling Main             ( eqFn.hs, eqFn.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.10.3 for i386-unknown-linux):
         Simplifier ticks exhausted
   When trying UnfoldingDone f_XOO
   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: 700804

 My program eqFn.hs:
 {{{
 {-# LANGUAGE FlexibleInstances #-}

 instance Eq a => Eq (Bool -> a) where
     f == g = f True == g True &&
              f False == g False

 nand a b = not (a && b)

 xor a b = nand (nand a c) (nand b c) where c=nand a b

 halfAdder a b = (xor a b, a && b) -- (sum, cOut)
 fullAdder cIn a b = let (s, c') = halfAdder a b
                         (sum, c'') = halfAdder cIn s
                     in (sum, c' || c'')

 adder2 cIn a0 b0 a1 b1 =
     let (o0, cTmp) = fullAdder cIn a0 b0
         (o1, cOut) = fullAdder cTmp a1 b1
     in (o0, o1, cOut)

 adder4 cIn a0 b0 a1 b1 a2 b2 a3 b3 =
     let (o0, o1, cTmp) = adder2 cIn a0 b0 a1 b1
         (o2, o3, cOut) = adder2 cTmp a2 b2 a3 b3
     in (o0, o1, o2, o3, cOut)

 adder8 cIn a0 b0 a1 b1 a2 b2 a3 b3 a4 b4 a5 b5 a6 b6 a7 b7 =
     let (o0, o1, o2, o3, cTmp) = adder4 cIn a0 b0 a1 b1 a2 b2 a3 b3
         (o4, o5, o6, o7, cOut) = adder4 cTmp a4 b4 a5 b5 a6 b6 a7 b7
     in (o0, o1, o2, o3, o4, o5, o6, o7, cOut)

 main = print (adder8 == adder8)
 }}}

 Btw, it works if I replace adder8 with adder4 in the last line.

 I think this is a bug because, if the problem is too complicated for the
 optimizer it should just skip that part instead of failing.

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


More information about the ghc-tickets mailing list