{-# LANGUAGE TypeFamilies #-}{-# LANGUAGE UnicodeSyntax #-}typeConstrda=Numa⇒adataADTa=ADT(Constrda)ExistentiallyLostdataExistentiallyLost=∀u.TCu⇒ExistentiallyLostuclassu~(ATF1u,ATF2u)⇒TCuwheretypeATF1u∷*typeATF2u∷*uie_handlers∷ADTInt-- Loop:-- - ADT depends on ExistentiallyLost (also the Constrd appendage)-- - ExistentiallyLost depends on TC-- - TC depends on ADT
-->
[1 of 1] Compiling Main ( /home/deepfire/src/ghc-testcases/tyconroles-sees-a-tctycon-tyalias.hs, interpreted )<- ghc: panic! (the 'impossible' happened) (GHC version 8.0.0.20160421 for x86_64-unknown-linux): tyConRoles sees a TcTyCon Constrd Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
Edited
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Child items
...
Show closed items
Linked items
0
Link issues together to show that they're related or that one is blocking others.
Learn more.
@_deepfire: Could you please change your testcase to not depend on base-unicode-symbols? That would make it easier to include it in the testsuite later. Thanks.
Note to others: you can uncomment import Prelude.Unicode and still reproduce the bug.
\r\n{{{\r\n\r\n[1 of 1] Compiling Main ( /home/deepfire/src/ghc-testcases/tyconroles-sees-a-tctycon-tyalias.hs, interpreted )\r\n<- ghc: panic! (the 'impossible' happened)\r\n (GHC version 8.0.0.20160421 for x86_64-unknown-linux):\r\n \ttyConRoles sees a TcTyCon Constrd\r\n\r\n Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug\r\n}}}","new":"{{{#!hs\r\n{-# LANGUAGE TypeFamilies #-}\r\n# LANGUAGE UnicodeSyntax #\r\n\r\ntype Constrd a = Num a ⇒ a\r\n\r\ndata ADT a = ADT (Constrd a) ExistentiallyLost\r\n\r\ndata ExistentiallyLost = ∀ u. TC u ⇒ ExistentiallyLost u\r\n\r\nclass u ~ (ATF1 u, ATF2 u) ⇒ TC u where\r\n type ATF1 u ∷ *\r\n type ATF2 u ∷ *\r\n uie_handlers ∷ ADT Int\r\n\r\n-- Loop:\r\n-- - ADT depends on ExistentiallyLost (also the Constrd appendage)\r\n-- - ExistentiallyLost depends on TC\r\n-- - TC depends on ADT\r\n}}}\r\n-->\r\n{{{\r\n\r\n[1 of 1] Compiling Main ( /home/deepfire/src/ghc-testcases/tyconroles-sees-a-tctycon-tyalias.hs, interpreted )\r\n<- ghc: panic! (the 'impossible' happened)\r\n (GHC version 8.0.0.20160421 for x86_64-unknown-linux):\r\n \ttyConRoles sees a TcTyCon Constrd\r\n\r\n Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug\r\n}}}"},"type_of_failure":{"old":null,"new":null},"blocking":{"old":null,"new":null}} -->
The problem is that Constrd is bogus because its right-hand side is constrained and we haven't enabled the right extensions. The validity check fails. Regardless, GHC tries to continue to check the remaining declarations. To do this, GHC replaces Constrd with a stubbed-out TyCon, as explained in this note:
{- Note [Recover from validity error]~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~We recover from a validity error in a type or class, which allows usto report multiple validity errors. In the failure case we return aTyCon of the right kind, but with no interesting behaviour(makeTyConAbstract). Why? Suppose we have type T a = Funwhere Fun is a type family of arity 1. The RHS is invalid, but wewant to go on checking validity of subsequent type declarations.So we replace T with an abstract TyCon which will do no harm.See indexed-types/should_fail/BadSock and Trac #10896Painfully, though, we *don't* want to do this for classes.Consider tcfail041: class (?x::Int) => C a where ... instance C IntThe class is invalid because of the superclass constraint. Butwe still want it to look like a /class/, else the instance bleatsthat the instance is mal-formed because it hasn't got a class inthe head.-}
Because of the changes caused by TypeInType, the solver now can run while checking type declarations, and the solver ends up seeing the stubbed-out TyCon, causing the panic.
What should be done about this? Here are some ideas:
Some up with a way to deal with the problem described in the Note without fully stubbing out the TyCon. For example, the bogus T in the note could be transmuted to a type family T a with no instances.
If there is a validity error in one mutually-recursive group, don't proceed to the next group. This will reduce the number of errors reported in one go.
Enlarge the stubbed-out TyCons to be able to make it through the solver without panicking. This shouldn't be too hard, but it seems like the wrong direction of travel.
In any case, I'm not assigning the ticket to myself, because I make no guarantees about my ability to finish this work. I just saw that TcTyCon (which is the current form of a stubbed-out TyCon) was causing trouble so I thought I'd take a look.
Happily, commit 0c9d9dec (Remove panics for TcTyCon, the fix for #13271 (closed)) fixed the two programs in this ticket. I've added regression tests for them in D3573.