[GHC] #12638: GHC panic when resolving Show instance

#12638: GHC panic when resolving Show instance -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: PolyKinds, | Operating System: Unknown/Multiple TypeFamilies | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I'm playing around with rolling my own type defaulting and found a panic. Note: adding a stub `Show (W a)` instance resolves this (i.e. `show _ = "test"`). {{{ {- Test.hs -} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeFamilies #-} module Test where import Data.Proxy data W (a :: k) = Wk | W (MkStar a) type family MkStar (a :: k) :: * main = print (W Proxy :: W (Proxy (~))) }}} {{{ $ ghc Test.hs -o test [1 of 1] Compiling Test ( Test.hs, Test.o ) Test.hs:13:8: error:ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-apple-darwin): print_equality ~ Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} If `x = W Proxy :: W (Proxy (~))` is only defined, there is no issue. It seems to occur exactly when resolving a `Show` instance for `W (Proxy (~))` and one does not exist. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12638 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12638: GHC panic when resolving Show instance -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: PolyKinds, Resolution: duplicate | TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12041 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: new => closed * resolution: => duplicate * related: => #12041 Comment: This is fixed on the master branch and 8.0 branch. Thanks for the report! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12638#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC