
#10403: GHC crashes on a partial type signature -------------------------------------+------------------------------------- Reporter: Artyom.Kazak | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: partial- Blocked By: | sigs/should_compile/T10403 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by int-index): Simon, could you please add the code from the ticket to the test case verbatim? Your new variation does not trigger the bug because you removed the `app` function. Since you want to test both `h1 :: _` and `h2 :: _ => _`, please do not forget to include `add1` and `add2` so they get called. Here's code that triggers the bug: {{{ {-# LANGUAGE PartialTypeSignatures #-} module T10403 where main :: IO () main = return () data I a = I a instance Functor I where fmap f (I a) = I (f a) newtype B t a = B a instance Functor (B t) where fmap f (B a) = B (f a) newtype H f = H (f ()) app1 :: H (B t) app1 = h1 (H . I) (B ()) app2 :: H (B t) app2 = h2 (H . I) (B ()) h1 :: _ => _ --h1 :: Functor m => (a -> b) -> m a -> H m h1 f b = (H . fmap (const ())) (fmap f b) h2 :: _ --h2 :: Functor m => (a -> b) -> m a -> H m h2 f b = (H . fmap (const ())) (fmap f b) }}} The error message I'm getting when loading it in GHCi is: {{{ GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help λ> :l Bug.hs [1 of 1] Compiling T10403 ( Bug.hs, interpreted ) Bug.hs:21:12: Couldn't match type ‘b’ with ‘H I’ ‘b’ is untouchable inside the constraints () bound by the type signature for app2 :: H (B t) at Bug.hs:20:9-15ghc: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-unknown-linux): No skolem info: b_ao6[sk] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10403#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler