[GHC] #12104: Type families, `TypeError`, and `-fdefer-type-errors` cause "opt_univ fell into a hole"

GHC ghc-devs at haskell.org
Fri May 27 17:16:42 UTC 2016


#12104: Type families, `TypeError`, and `-fdefer-type-errors` cause "opt_univ fell
into a hole"
-------------------------------------+-------------------------------------
        Reporter:  antalsz           |                Owner:
            Type:  bug               |               Status:  new
        Priority:  high              |            Milestone:
       Component:  Compiler          |              Version:  8.0.1
      Resolution:                    |             Keywords:  TypeFamilies,
                                     |  CustomTypeErrors
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Compile-time      |  Unknown/Multiple
  crash                              |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by thomie):

 * priority:  normal => high
 * os:  MacOS X => Unknown/Multiple
 * architecture:  x86_64 (amd64) => Unknown/Multiple


@@ -11,0 +11,2 @@
+
+ module T12104 where

New description:

 If I create a type family – open or closed – with a case that evaluates to
 a `TypeError`, and define a top-level binding with this type, loading the
 file with `-fdefer-type-errors` enabled (or via `:load!`/`:reload!`)
 panics GHC with "opt_univ fell into a hole".  (And if I used `:load!` or
 `:reload!`, `-fdefer-type-errors` doesn't get unset.)

 A minimal example:

 {{{#!hs
 {-# LANGUAGE TypeFamilies, DataKinds, UndecidableInstances #-}

 module T12104 where

 import GHC.TypeLits

 type family F a where
   F a = TypeError (Text "error")

 err :: F ()
 err = ()
 }}}

 results in the panic

 {{{
 ….hs:9:7: warning: [-Wdeferred-type-errors]
     • error
     • In the expression: ()
       In an equation for ‘err’: err = ()
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.0.1 for x86_64-apple-darwin):
         opt_univ fell into a hole {a4Va}
 }}}

 Adding more cases to the type family, or making it open, still cause the
 crash.  This holds whether the error case is a final catch-all case, or
 something more like

 {{{#!hs
 type family F a where
   F () = TypeError (Text "error")
   F a  = ()
 }}}

 Just using a type synonym for `F` doesn't cause a panic, however, and nor
 does giving `err` the type `TypeError (Text "error")` directly.

--

Comment:

 Confirmed with HEAD (8.1.20160520).

 Also reproducible by running just
 {{{
 ghc -fdefer-type-errors type-families-TypeError-defer-type-errors-
 opt_univ-bug.hs
 }}}

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


More information about the ghc-tickets mailing list