[GHC] #13381: "opt_univ fell into a hole" panic from rewrite rule

GHC ghc-devs at haskell.org
Mon Mar 6 03:57:42 UTC 2017


#13381: "opt_univ fell into a hole" panic from rewrite rule
-------------------------------------+-------------------------------------
           Reporter:  dfeuer         |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.2.1
          Component:  Compiler       |           Version:  8.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Compile-time
  Unknown/Multiple                   |  crash or panic
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Roboguy reports (via IRC) that the following causes a GHC panic:

 {{{#!hs
 {-# LANGUAGE RankNTypes #-}

 module Crash where

 data Exp a = Exp

 fromExp :: Exp a -> a
 fromExp _ = error "Impossible"

 toExp :: a -> Exp a
 toExp _ = Exp



 newtype Iter a b = Iter { getIter :: forall r. (a -> r) -> (b -> r) -> r }

 iterLoop :: (a -> Iter a b) -> a -> b
 iterLoop f x = getIter (f x) (iterLoop f) id


   -- This rewrite rule results in a GHC panic: "opt_univ fell into a hole"
 on GHC 8.0.1, 8.0.2, and 8.1.
 {-# RULES "fromExp-into-iterLoop" [~]
     forall (f :: Int -> Iter (Exp Int) (Exp Char))
            (init :: Int).
     fromExp (iterLoop f init)
       =
     fromExp (iterLoop (f . fromExp) (toExp init))
   #-}
 }}}

 I have confirmed this, and see the following error:

 {{{
 ghc-stage2: panic! (the 'impossible' happened)
   (GHC version 8.1.20170305 for x86_64-unknown-linux):
         opt_univ fell into a hole
   {a1WD}
   Call stack:
       CallStack (from HasCallStack):
         prettyCurrentCallStack, called at
 compiler/utils/Outputable.hs:1191:58 in ghc:Outputable
         callStackDoc, called at compiler/utils/Outputable.hs:1195:37 in
 ghc:Outputable
         pprPanic, called at compiler/types/OptCoercion.hs:398:29 in
 ghc:OptCoercion
 }}}

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


More information about the ghc-tickets mailing list