[GHC] #15984: Backpack accepts ill-kinded instantiations. Can cause GHC panic

#15984: Backpack accepts ill-kinded instantiations. Can cause GHC panic -------------------------------------+------------------------------------- Reporter: aaronvargo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.3 Component: Compiler | Version: 8.6.2 Keywords: backpack | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Given the following: {{{#!hs {-# language KindSignatures #-} signature A where data A :: * }}} {{{#!hs module Foo where import A foo :: A -> A foo = id }}} {{{#!hs module IllKindedA where type A = Maybe }}} GHC allows the signature `A` to be instantiated with `IllKindedA`: {{{ mixins: foo (Foo as Bug) requires (A as IllKindedA) }}} Using the resulting module can cause odd errors or a panic. E.g. the following causes a panic: {{{#!hs module Bar where import Bug bar = foo }}} {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.6.2 for x86_64-unknown-linux): getRuntimeRep A :: * -> * Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:2049:18 in ghc:Type }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15984 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15984: Backpack accepts ill-kinded instantiations. Can cause GHC panic -------------------------------------+------------------------------------- Reporter: aaronvargo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.3 Component: Compiler | Version: 8.6.2 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Old description:
Given the following:
{{{#!hs {-# language KindSignatures #-} signature A where
data A :: * }}}
{{{#!hs module Foo where
import A
foo :: A -> A foo = id }}}
{{{#!hs module IllKindedA where
type A = Maybe }}}
GHC allows the signature `A` to be instantiated with `IllKindedA`:
{{{ mixins: foo (Foo as Bug) requires (A as IllKindedA) }}}
Using the resulting module can cause odd errors or a panic. E.g. the following causes a panic:
{{{#!hs module Bar where
import Bug
bar = foo }}}
{{{ ghc: panic! (the 'impossible' happened) (GHC version 8.6.2 for x86_64-unknown-linux): getRuntimeRep A :: * -> * Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:2049:18 in ghc:Type }}}
New description: Given the following: {{{#!hs {-# language KindSignatures #-} signature A where data A :: * }}} {{{#!hs module Foo where import A foo :: A -> A foo = id }}} {{{#!hs module IllKindedA where type A = Maybe }}} GHC allows the signature `A` to be instantiated with `IllKindedA`: {{{ mixins: foo (Foo as Bug) requires (A as IllKindedA) }}} Using the resulting module can cause odd errors or a panic. E.g. the following causes a panic: {{{#!hs module Bar where import Bug bar = foo }}} {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.6.2 for x86_64-unknown-linux): getRuntimeRep A :: * -> * Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:2049:18 in ghc:Type }}} -- Comment (by aaronvargo): Oops, it seems this only happened because I foolishly had `IllKindedA` in the same library as `A`: {{{ library foo build-depends: base signatures: A exposed-modules: Foo, IllKindedA library bar build-depends: base, foo exposed-modules: Bar mixins: foo (Foo as Bug) requires (A as IllKindedA) }}} It's still a bug though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15984#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC