[GHC] #9106: GHC Panic related to functional dependencies - kindFunResult

#9106: GHC Panic related to functional dependencies - kindFunResult ----------------------------+--------------------------------------- Reporter: yuriy | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Keywords: | Operating System: Windows Architecture: x86 | Type of failure: Compile-time crash Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ----------------------------+--------------------------------------- Minimal example: {{{ {-# LANGUAGE MultiParamTypeClasses, DataKinds, FunctionalDependencies, TypeOperators, KindSignatures, PolyKinds, FlexibleInstances, FlexibleContexts, UndecidableInstances #-} import GHC.TypeLits data Proxy (a :: k) = Proxy class FunctorN n f a fa | n f a -> fa where fmapn :: Proxy n -> Proxy f -> (a -> a) -> fa -> fa instance FunctorN 0 f a a where fmapn _ _ a = a instance (Functor f, FunctorN (n - 1) f a fa) => FunctorN n f a (f fa) where fmapn _ pf f = fmap (fmapn (Proxy :: Proxy (n-1)) pf f) }}} Crashes with ghc and ghci: {{{
ghc test [1 of 1] Compiling Main ( test.hs, test.o ) ghc.exe: panic! (the 'impossible' happened) (GHC version 7.8.20140130 for x86_64-unknown-mingw32): kindFunResult k{tv azb} [sk]
ghci test GHCi, version 7.8.20140130: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling Main ( test.hs, interpreted ) ghc.exe: panic! (the 'impossible' happened) (GHC version 7.8.20140130 for x86_64-unknown-mingw32): kindFunResult k{tv aPm} [sk] }}}
Removing the functional dependency makes the code compile. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9106 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9106: GHC Panic related to functional dependencies - kindFunResult ---------------------------------------+--------------------------- Reporter: yuriy | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86 Type of failure: Compile-time crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: ---------------------------------------+--------------------------- Comment (by yuriy): The same code without {{{GHC.TypeLits}}} works: {{{ {-# LANGUAGE MultiParamTypeClasses, DataKinds, FunctionalDependencies, TypeOperators, KindSignatures, PolyKinds, FlexibleInstances, FlexibleContexts, UndecidableInstances, ScopedTypeVariables #-} data Proxy (a :: k) = Proxy data Nat = Z | P Nat class FunctorN n f a fa | n f a -> fa where fmapn :: Proxy n -> Proxy f -> (a -> a) -> fa -> fa instance FunctorN Z f a a where fmapn _ _ a = a instance (Functor f, FunctorN n f a fa) => FunctorN (P n) f a (f fa) where fmapn _ pf f = fmap (fmapn (Proxy :: Proxy n) pf f) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9106#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9106: GHC Panic related to functional dependencies - kindFunResult ---------------------------------------+--------------------------- Reporter: yuriy | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86 Type of failure: Compile-time crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: ---------------------------------------+--------------------------- Comment (by darchon): Also annotating the `Z` instance with an explicit kind, `(f :: *)`, makes the `GHC.TypeLits` version work: {{{ {-# LANGUAGE MultiParamTypeClasses, DataKinds, FunctionalDependencies, TypeOperators, KindSignatures, PolyKinds, FlexibleInstances, FlexibleContexts, UndecidableInstances, ScopedTypeVariables #-} module FunctorN where import GHC.TypeLits data Proxy (a :: k) = Proxy class FunctorN n f a fa | n f a -> fa where fmapn :: Proxy n -> Proxy f -> (a -> a) -> fa -> fa instance FunctorN 0 (f :: *) a a where fmapn _ _ a = a instance (Functor f, FunctorN (n - 1) f a fa) => FunctorN n f a (f fa) where fmapn _ pf f = fmap (fmapn (Proxy :: Proxy (n-1)) pf f) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9106#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9106: GHC Panic related to functional dependencies - kindFunResult ---------------------------------------+--------------------------- Reporter: yuriy | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86 Type of failure: Compile-time crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: ---------------------------------------+--------------------------- Comment (by darchon): The type family version also works: {{{ {-# LANGUAGE DataKinds, FlexibleInstances, MultiParamTypeClasses, PolyKinds, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-} module FunctorN where import GHC.TypeLits data Proxy (a :: k) = Proxy type family F n f a where F 0 f a = a F n f a = f (F (n-1) f a) class F n f a ~ fa => FunctorN n f a fa where fmapn :: Proxy n -> Proxy f -> (a -> a) -> fa -> fa instance FunctorN 0 f a a where fmapn _ _ a = a instance ( Functor f, FunctorN (n-1) f a fa, F (n - 1) f a ~ fa , F n f a ~ f fa) => FunctorN n f a (f fa) where fmapn _ pf f = fmap (fmapn (Proxy :: Proxy (n-1)) pf f) test :: Maybe (Maybe (Maybe Int)) test = fmapn (Proxy :: Proxy 3) (Proxy :: Proxy Maybe) (+1) (Just (Just (Just 3))) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9106#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9106: GHC Panic related to functional dependencies - kindFunResult ---------------------------------------+--------------------------- Reporter: yuriy | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86 Type of failure: Compile-time crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: ---------------------------------------+--------------------------- Comment (by simonpj): I'm working on this... I know more or less what's happening. Thanks for the examples -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9106#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9106: GHC Panic related to functional dependencies - kindFunResult
---------------------------------------+---------------------------
Reporter: yuriy | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.2
Resolution: | Keywords:
Operating System: Windows | Architecture: x86
Type of failure: Compile-time crash | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
---------------------------------------+---------------------------
Comment (by Simon Peyton Jones

#9106: GHC Panic related to functional dependencies - kindFunResult ---------------------------------------+--------------------------- Reporter: yuriy | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86 Type of failure: Compile-time crash | Difficulty: Unknown Test Case: polykinds/T9106 | Blocked By: Blocking: | Related Tickets: ---------------------------------------+--------------------------- Changes (by simonpj): * status: new => merge * testcase: => polykinds/T9106 Comment: Thank you. I've fixed the crash. Now we get {{{ T9106.hs:13:10: Illegal instance declaration for ‘FunctorN n f a (f fa)’ The liberal coverage condition fails in class ‘FunctorN’ for functional dependency: ‘n f a -> fa’ Reason: lhs types ‘n’, ‘f’, ‘a’ do not jointly determine rhs type ‘f fa’ In the instance declaration for ‘FunctorN n f a (f fa)’ }}} which looks right to me. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9106#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9106: GHC Panic related to functional dependencies - kindFunResult ---------------------------------------+--------------------------- Reporter: yuriy | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Windows | Architecture: x86 Type of failure: Compile-time crash | Difficulty: Unknown Test Case: polykinds/T9106 | Blocked By: Blocking: | Related Tickets: ---------------------------------------+--------------------------- Changes (by thoughtpolice): * status: merge => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9106#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9106: GHC Panic related to functional dependencies - kindFunResult
---------------------------------------+--------------------------------
Reporter: yuriy | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone: 7.8.3
Component: Compiler | Version: 7.8.2
Resolution: fixed | Keywords:
Operating System: Windows | Architecture: x86
Type of failure: Compile-time crash | Test Case: polykinds/T9106
Blocked By: | Blocking:
Related Tickets: |
---------------------------------------+--------------------------------
Comment (by Simon Peyton Jones
participants (1)
-
GHC