
#15351: QuantifiedConstraints ignore FunctionalDependencies -------------------------------------+------------------------------------- Reporter: aaronvargo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Keywords: Resolution: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by aaronvargo: Old description:
The following code fails to compile:
{{{#!hs {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE FunctionalDependencies #-}
class C a b | a -> b where foo :: a -> b
bar :: (forall a. C (f a) Int) => f a -> String bar = show . foo }}}
{{{ • Could not deduce (Show a0) arising from a use of ‘show’ ... The type variable ‘a0’ is ambiguous }}}
Yet it ought to work, since this is perfectly fine with top-level instances:
{{{#!hs instance C [a] Int where ...
baz :: [a] -> String baz = show . foo }}}
New description: The following code fails to compile: {{{#!hs {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE FunctionalDependencies #-} class C a b | a -> b where foo :: a -> b bar :: (forall a. C (f a) Int) => f a -> String bar = show . foo }}} {{{ • Could not deduce (Show a0) arising from a use of ‘show’ ... The type variable ‘a0’ is ambiguous • Could not deduce (C (f a) a0) arising from a use of ‘foo’ ... The type variable ‘a0’ is ambiguous }}} Yet it ought to work, since this is perfectly fine with top-level instances: {{{#!hs instance C [a] Int where ... baz :: [a] -> String baz = show . foo }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15351#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler