[GHC] #9574: GHC Panic: No Skolem Info

#9574: GHC Panic: No Skolem Info -------------------------------------+------------------------------------- Reporter: ian_mi | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- GHC 7.8.3 and from git both panic with Couldn't match kind ‘o1’ with ‘(,) o o’ ‘o1’ is untouchable inside the constraints (Object (c :><: c) a) bound by a type expected by the context: Object (c :><: c) a => Tagged a (c (FMap (ProductF c) a) (FMap (Proj2 c c) a)) at Product.hs:35:9-15ghc: panic! (the 'impossible' happened) (GHC version 7.9.20140908 for x86_64-unknown-linux): No skolem info: o1_a6XS I have not yet attempted to reduce the problem at all. The offending code is the use of fmap here: {{{#!hs proj2 :: forall (c :: o -> o -> *). ProductCategory c => NatTr (c :><: c) c (ProductF c) (Proj2 c c) proj2 = NatTr t where NatTr t = fmap (CompF Proj2 IdentityF) e e :: NatTr (c :><: c) (c :><: c) (Comp ('KProxy :: KProxy o) (Diag c) (ProductF c)) (IdentityF (c :><: c)) e = counit }}} fmap is defined as {{{#!hs fmap :: forall f (a :: o1) (b :: o1). Functor f ('KProxy :: KProxy (o1 -> o2)) => f -> Domain f a b -> Codomain f (FMap f a :: o2) (FMap f b :: o2) fmap _ = proxy morphMap (Proxy :: Proxy f) }}} while CompF is defined by {{{#!hs data CompF f g (k :: KProxy (o3 -> o4, o1 -> o2)) where CompF :: (Functor f ('KProxy :: KProxy (o3 -> o4)), Functor g ('KProxy :: KProxy (o1 -> o2))) => f -> g -> CompF f g ('KProxy :: KProxy (o3 -> o4, o1 -> o2)) }}} This makes some sense because there is a functional dependency between the functor and the kind proxy. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9574 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9574: GHC Panic: No Skolem Info -------------------------------------+------------------------------------- Reporter: ian_mi | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Old description:
GHC 7.8.3 and from git both panic with
Couldn't match kind ‘o1’ with ‘(,) o o’ ‘o1’ is untouchable inside the constraints (Object (c :><: c) a) bound by a type expected by the context: Object (c :><: c) a => Tagged a (c (FMap (ProductF c) a) (FMap (Proj2 c c) a)) at Product.hs:35:9-15ghc: panic! (the 'impossible' happened) (GHC version 7.9.20140908 for x86_64-unknown-linux): No skolem info: o1_a6XS
I have not yet attempted to reduce the problem at all. The offending code is the use of fmap here:
{{{#!hs proj2 :: forall (c :: o -> o -> *). ProductCategory c => NatTr (c :><: c) c (ProductF c) (Proj2 c c) proj2 = NatTr t where NatTr t = fmap (CompF Proj2 IdentityF) e e :: NatTr (c :><: c) (c :><: c) (Comp ('KProxy :: KProxy o) (Diag c) (ProductF c)) (IdentityF (c :><: c)) e = counit }}}
fmap is defined as
{{{#!hs fmap :: forall f (a :: o1) (b :: o1). Functor f ('KProxy :: KProxy (o1 -> o2)) => f -> Domain f a b -> Codomain f (FMap f a :: o2) (FMap f b :: o2) fmap _ = proxy morphMap (Proxy :: Proxy f) }}}
while CompF is defined by
{{{#!hs data CompF f g (k :: KProxy (o3 -> o4, o1 -> o2)) where CompF :: (Functor f ('KProxy :: KProxy (o3 -> o4)), Functor g ('KProxy :: KProxy (o1 -> o2))) => f -> g -> CompF f g ('KProxy :: KProxy (o3 -> o4, o1 -> o2)) }}}
This makes some sense because there is a functional dependency between the functor and the kind proxy.
New description: GHC 7.8.3 and from git both panic with {{{ Couldn't match kind ‘o1’ with ‘(,) o o’ ‘o1’ is untouchable inside the constraints (Object (c :><: c) a) bound by a type expected by the context: Object (c :><: c) a => Tagged a (c (FMap (ProductF c) a) (FMap (Proj2 c c) a)) at Product.hs:35:9-15ghc: panic! (the 'impossible' happened) (GHC version 7.9.20140908 for x86_64-unknown-linux): No skolem info: o1_a6XS }}} I have not yet attempted to reduce the problem at all. The offending code is the use of fmap here: {{{#!hs proj2 :: forall (c :: o -> o -> *). ProductCategory c => NatTr (c :><: c) c (ProductF c) (Proj2 c c) proj2 = NatTr t where NatTr t = fmap (CompF Proj2 IdentityF) e e :: NatTr (c :><: c) (c :><: c) (Comp ('KProxy :: KProxy o) (Diag c) (ProductF c)) (IdentityF (c :><: c)) e = counit }}} fmap is defined as {{{#!hs fmap :: forall f (a :: o1) (b :: o1). Functor f ('KProxy :: KProxy (o1 -> o2)) => f -> Domain f a b -> Codomain f (FMap f a :: o2) (FMap f b :: o2) fmap _ = proxy morphMap (Proxy :: Proxy f) }}} while CompF is defined by {{{#!hs data CompF f g (k :: KProxy (o3 -> o4, o1 -> o2)) where CompF :: (Functor f ('KProxy :: KProxy (o3 -> o4)), Functor g ('KProxy :: KProxy (o1 -> o2))) => f -> g -> CompF f g ('KProxy :: KProxy (o3 -> o4, o1 -> o2)) }}} This makes some sense because there is a functional dependency between the functor and the kind proxy. -- Comment (by simonpj): Clearly a bug, but there's virtually no chance of fixing it without a way to reproduce it, alas. So if you felt able to do that, it'd be great. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9574#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9574: GHC Panic: No Skolem Info -------------------------------------+------------------------------------- Reporter: ian_mi | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by monoidal): * status: new => infoneeded Comment: @ian_mi: can you provide a testcase, even if it's huge or depends on hackage libraries? I can try to reduce it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9574#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9574: GHC Panic: No Skolem Info -------------------------------------+------------------------------------- Reporter: ian_mi | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by ian_mi): Sure. I've been trying to reduce it myself but it's been somewhat tricky. I will put together an unreduced example instead. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9574#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9574: GHC Panic: No Skolem Info -------------------------------------+------------------------------------- Reporter: ian_mi | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by monoidal): Bumping. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9574#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9574: GHC Panic: No Skolem Info -------------------------------------+------------------------------------- Reporter: ian_mi | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by ian_mi): * status: infoneeded => new Comment: Sorry for the delay, here is how this bug can be reproduced: 1. Clone the extended-categories package from https://github.com/ian-mi /extended-categories and checkout tag `0.2.0`. 2. Install the dependencies `tagged` and `constraints` into a sandbox if not already available. 3. Download the attached `Bug9574.hs` file. 3. Using GHC 7.8.3, load extended-categories into ghci using `cabal repl` and then load `Bug9574.hs`. Please let me know if you need any additional information. Thanks, Ian -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9574#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9574: GHC Panic: No Skolem Info -------------------------------------+------------------------------------- Reporter: ian_mi | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by monoidal): I reduced the panic to this (to reproduce just run `ghci Bug9574`). It makes 7.9 panic but not 7.8, likely by accident though. {{{ {-# LANGUAGE PolyKinds, DataKinds, TypeFamilies, ScopedTypeVariables, GADTs, RankNTypes #-} module Bug9574 where data KProxy (t :: *) = KProxy data Proxy p class Funct f where type Codomain f :: * instance Funct ('KProxy :: KProxy o) where type Codomain 'KProxy = NatTr (Proxy :: o -> *) data NatTr (c :: o -> *) where M :: (forall (a :: o). Proxy a) -> NatTr (c :: o -> *) p :: forall (c :: o -> *). NatTr c p = M t where M t = undefined :: Codomain ('KProxy :: KProxy o) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9574#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9574: GHC Panic: No Skolem Info
-------------------------------------+-------------------------------------
Reporter: ian_mi | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.9
Resolution: | Keywords:
Operating System: | Architecture: Unknown/Multiple
Unknown/Multiple | Difficulty: Unknown
Type of failure: | Blocked By:
None/Unknown | Related Tickets:
Test Case: |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#9574: GHC Panic: No Skolem Info -------------------------------------+------------------------------------- Reporter: ian_mi | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: fixed | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | polykinds/T9574 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => polykinds/T9574 * resolution: => fixed Comment: Thank you for reducing the test case so well. The problem is that the instance {{{ instance Funct ('KProxy :: KProxy o) where type Codomain 'KProxy = NatTr (Proxy :: o -> *) }}} should bind 'o' on the LHS of the type instance: {{{ instance Funct ('KProxy :: KProxy o) where type Codomain ('KProxy :: KProxy o) = NatTr (Proxy :: o -> *) }}} Otherwise there is nothing to connect the lhs and rhs. I've added this check. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9574#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9574: GHC Panic: No Skolem Info
-------------------------------------+-------------------------------------
Reporter: ian_mi | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.9
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| polykinds/T9574
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
-------------------------------------+-------------------------------------
Comment (by Ryan Scott
participants (1)
-
GHC