#6015: "No instance" when using PolyKinds/DataKinds/FunDeps/Undecidable
---------------------------------------+------------------------------------
Reporter: atnnn | Owner:
Type: feature request | Status: new
Priority: normal | Component: Compiler
Version: 7.4.1 | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: GHC rejects valid program | Testcase:
Blockedby: | Blocking:
Related: |
---------------------------------------+------------------------------------
Comment(by atnnn):
I have been poking at the GHC source to see if I can get this to
typecheck. Here is a simpler example that does not use `DataKinds` or
`UndecidableInstances`.
{{{
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances,
FunctionalDependencies #-}
-- {-# LANGUAGE PolyKinds #-}
class Foo a b | a -> b
instance Foo a ()
foo :: Foo () b => b
foo = undefined
}}}
Without `PolyKinds`, GHCi doesn't complain about the type
{{{
>>> foo
*** Exception: Prelude.undefined
}}}
Uncommenting the `PolyKinds` pragma makes GHCi complain.
{{{
>>> foo
No instance for (Foo * * () b0) arising from a use of `foo'
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/6015#comment:1>
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