[GHC] #9106: GHC Panic related to functional dependencies - kindFunResult
GHC
ghc-devs at haskell.org
Tue May 13 21:29:38 UTC 2014
#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
More information about the ghc-tickets
mailing list