#6015: "No instance" when using PolyKinds/DataKinds/FunDeps/Undecidable
----------------------------------------+-----------------------------------
Reporter: atnnn | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.4.1
Resolution: | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: GHC rejects valid program | Difficulty: Unknown
Testcase: polykinds/T6015 | Blockedby:
Blocking: | Related:
----------------------------------------+-----------------------------------
Changes (by atnnn):
* status: closed => new
* resolution: fixed =>
Comment:
Thanks Simon.
Here is an extra one line patch that substitutes the kind variables that
your fix now let's through. Without it, the following code panics.
{{{
{-# LANGUAGE PolyKinds, KindSignatures, FunctionalDependencies,
FlexibleInstances,
UndecidableInstances, TypeOperators, DataKinds,
FlexibleContexts #-}
import Prelude hiding ((++))
data T a = T
class ((a :: [k]) ++ (b :: [k])) (c :: [k]) | a b -> c
instance ('[] ++ b) b
instance (a ++ b) c => ((x ': a) ++ b) (x ': c)
test = T :: ('[True] ++ '[]) l => T l
}}}
This may be what the TODO in `TcInteract.instFunDepEqn` is about.
{{{
; tys' <- mapM instFlexiTcS tvs -- IA0_TODO: we might need to do
kind substitution
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/6015#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs