[GHC] #10403: GHC crashes on a partial type signature

#10403: GHC crashes on a partial type signature -------------------------------------+------------------------------------- Reporter: | Owner: Artyom.Kazak | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Compiler | Operating System: Linux Keywords: | Type of failure: Compile-time Architecture: x86_64 | crash (amd64) | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- The following code crashes GHC 7.10.1 as is, but doesn't result in a crash if the signature is specified completely or isn't specified at all (inferred): {{{#!hs {-# LANGUAGE PartialTypeSignatures #-} module Main where 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 ()) app :: H (B t) app = h (H . I) (B ()) h :: _ --h :: Functor m => (a -> b) -> m a -> H m h f b = (H . fmap (const ())) (fmap f b) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10403 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Artyom.Kazak): * cc: vlad.z.4096@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10403#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by Artyom.Kazak: Old description:
The following code crashes GHC 7.10.1 as is, but doesn't result in a crash if the signature is specified completely or isn't specified at all (inferred):
{{{#!hs {-# LANGUAGE PartialTypeSignatures #-} module Main where
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 ())
app :: H (B t) app = h (H . I) (B ())
h :: _ --h :: Functor m => (a -> b) -> m a -> H m h f b = (H . fmap (const ())) (fmap f b) }}}
New description: The following code crashes GHC 7.10.1 as is, but doesn't result in a crash if the signature is specified completely or isn't specified at all (inferred): {{{#!hs {-# LANGUAGE PartialTypeSignatures #-} module Main 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 ()) app :: H (B t) app = h (H . I) (B ()) h :: _ --h :: Functor m => (a -> b) -> m a -> H m h f b = (H . fmap (const ())) (fmap f b) }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10403#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by lelf): Seems to work correctly for HEAD-20150403 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10403#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Artyom.Kazak): Error message (in GHCi 7.10.1): {{{#!hs $ ghci GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help Prelude Control.Applicative Control.Monad Data.Ratio> :l Bug.hs [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:18:10: Couldn't match type `b' with `H I' `b' is untouchable inside the constraints () bound by the type signature for app :: H (B t) at Bug.hs:17:8-14ghc: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-unknown-linux): No skolem info: b_aFd[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:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Artyom.Kazak): Possibly (most likely?) a duplicate of #10045. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10403#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10403: GHC crashes on a partial type signature -------------------------------------+------------------------------------- Reporter: Artyom.Kazak | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: Seems ok in 7.10 too. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10403#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10403: GHC crashes on a partial type signature
-------------------------------------+-------------------------------------
Reporter: Artyom.Kazak | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: fixed | Keywords:
Operating System: Linux | Architecture: x86_64
Type of failure: Compile-time | (amd64)
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Austin Seipp

#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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Artyom.Kazak): * status: closed => new * resolution: fixed => Comment: Can the testcase in Simon's `Test Trac #10403` commit be changed to how it should be? `h :: _ => _` doesn't trigger the bug, only `h :: _` does (and I don't know why Simon changed it). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10403#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#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:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10403: GHC crashes on a partial type signature -------------------------------------+------------------------------------- Reporter: Artyom.Kazak | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | 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: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => partial-sigs/should_compile/T10403 * resolution: => fixed Comment: I've elaborate the test to check both `h :: _` and `h :: _ => _`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10403#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: -------------------------------------+------------------------------------- Changes (by int-index): * status: closed => new * resolution: fixed => -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10403#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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 Simon Peyton Jones

#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 simonpj): OK, I've elaborated the test with the extra pieces you suggest. It all works fine in HEAD. It does not work in 7.10; and, as you'll see in #10045, we don't propose to fix in 7.10. I hope you can live without it. Sound OK? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10403#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10403: GHC crashes on a partial type signature -------------------------------------+------------------------------------- Reporter: Artyom.Kazak | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | 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: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10403#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10403: GHC crashes on a partial type signature -------------------------------------+------------------------------------- Reporter: Artyom.Kazak | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | 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): Yes, it sounds ok. I just wanted to make sure that the bug is known of and reflected in the test suite. Thanks. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10403#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC