[GHC] #12242: panic with complicated type/kind/class expressions

#12242: panic with complicated type/kind/class expressions -------------------------------------+------------------------------------- Reporter: Ashley | Owner: Yakeley | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: GHC rejects (amd64) | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I tried to simplify this as much as I could, but I couldn't boil it down further than this: {{{#!hs -- ghc -O -ddump-hi -ddump-to-file Bug.hs {-# LANGUAGE TypeInType #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE GADTs #-} module Bug where { import Data.Kind; data HetEq (a :: ka) (b :: kb) where { ReflH :: forall (k :: *) (t :: k). HetEq t t; }; data Rep :: forall (k :: *). k -> * where { SimpleRep :: forall (k :: *) (a :: k). Rep a; ApplyRep :: forall (k1 :: *) (k2 :: *) (p :: k1 -> k2) (a :: k1). Rep p -> Rep a -> Rep (p a); }; class TestHetEquality (w :: forall k. k -> *) where { testHetEquality :: forall (ka :: *) (a :: ka) (kb :: *) (b :: kb). w a -> w b -> Maybe (HetEq a b); }; instance TestHetEquality Rep where { testHetEquality (ApplyRep tfa ta) (ApplyRep tfb tb) = do { ReflH <- testHetEquality tfa tfb; ReflH <- testHetEquality ta tb; return ReflH; }; testHetEquality _ _ = Nothing; }; bug :: forall (a :: *). Rep (Maybe a) -> Maybe (Rep a); bug (ApplyRep tf ta) = case testHetEquality tf SimpleRep of { Just ReflH -> Just ta; Nothing -> Nothing; }; bug _ = Nothing; } }}} You'll need `-O` and `-ddump-hi` to trigger it. {{{ $ stack exec -- ghc -O -ddump-hi -ddump-to-file Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): pprIfaceCo Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12242 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12242: panic with complicated type/kind/class expressions -------------------------------------+------------------------------------- Reporter: Ashley Yakeley | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ashley Yakeley): Using `resolver: nightly-2016-06-27` in my `stack.yaml`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12242#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12242: panic with complicated type/kind/class expressions -------------------------------------+------------------------------------- Reporter: Ashley Yakeley | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => simonpj Comment: Stupid inexhaustive case in pretty printing for `IfaceCo`. I'll fix. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12242#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12242: panic with complicated type/kind/class expressions
-------------------------------------+-------------------------------------
Reporter: Ashley Yakeley | Owner: simonpj
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64
Type of failure: GHC rejects | (amd64)
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#12242: panic with complicated type/kind/class expressions -------------------------------------+------------------------------------- Reporter: Ashley Yakeley | Owner: simonpj Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge Comment: Pls merge. I didn't think it was worth a regression test -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12242#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12242: panic with complicated type/kind/class expressions
-------------------------------------+-------------------------------------
Reporter: Ashley Yakeley | Owner: simonpj
Type: bug | Status: merge
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64
Type of failure: GHC rejects | (amd64)
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#12242: panic with complicated type/kind/class expressions -------------------------------------+------------------------------------- Reporter: Ashley Yakeley | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.0.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12242#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC