[GHC] #12473: Ambiguous type var with DefaultSignatures and FunctionalDependencies

#12473: Ambiguous type var with DefaultSignatures and FunctionalDependencies -------------------------------------+------------------------------------- Reporter: dylex | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | 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: -------------------------------------+------------------------------------- Consider: {{{ {-# LANGUAGE DefaultSignatures, FunctionalDependencies, ScopedTypeVariables #-} class Foo a b where foo :: a -> b -> Int class Bar a b | b -> a where get :: b -> a bar :: b -> Int default bar :: Foo a b => b -> Int bar b = foo (get b :: a) b }}} This works fine with ghc 7.10.3 (even without the explicit :: a type spec), but with 8.0.1, produces: {{{ - Could not deduce (Foo a0 b) from the context: Foo a b bound by the type signature for: bar :: Foo a b => b -> Int at t.hs:6:3-17 The type variable `a0' is ambiguous - In the ambiguity check for `bar' To defer the ambiguity check to use sites, enable AllowAmbiguousTypes When checking the class method: bar :: forall a b. Bar a b => b -> Int In the class declaration for `Bar' }}} Not sure if this is intentional or some good way to get around it, but I couldn't find anything related to it in the release notes or any similar looking bugs. (Real-life case: https://github.com/dylex/postgresql- typed/blob/master/Database/PostgreSQL/Typed/Dynamic.hs#L48 ) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12473 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12473: Ambiguous type var with DefaultSignatures and FunctionalDependencies -------------------------------------+------------------------------------- Reporter: dylex | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: 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: | -------------------------------------+------------------------------------- Comment (by goldfire): There is a fine workaround: `-XAllowAmbiguousTypes`, as the error message suggests. But I tend to agree that this is incorrect behavior by GHC: should we be doing an ambiguity check on generic-default signatures? I think not. Why not? Because we never call a function with the type given by a generic-default signature. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12473#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12473: Ambiguous type var with DefaultSignatures and FunctionalDependencies -------------------------------------+------------------------------------- Reporter: dylex | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: 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: | -------------------------------------+------------------------------------- Comment (by simonpj): But we ''do'' call a function with the type given by the generic default signature! In effect the generic-default declaration gives rise to a definition {{{ $gdm_bar :: forall a b. (Bar a b, Foo a b) => b -> Int $gdm_bar b = foo (get b :: a) b }}} In an instance declaration where you do not give a declaration for `bar`, we fill in with this generic default method. That is {{{ instance blah => Bar t1 t2 where {} }}} becomes {{{ instance blah => Bar t1 t2 where bar = $gdm_bar }}} If the type of `$gdm_bar` was ambiguous, this really would be a problem. But in this case it isn't! I'll investigate -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12473#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12473: Ambiguous type var with DefaultSignatures and FunctionalDependencies -------------------------------------+------------------------------------- Reporter: dylex | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: 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: | -------------------------------------+------------------------------------- Comment (by simonpj): Happily, this is (I am almost certain) a dup of #12151, which is both fixed, and merged to the 8.0.2 branch. So worth checking that this works with 8.0.2, then close. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12473#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12473: Ambiguous type var with DefaultSignatures and FunctionalDependencies -------------------------------------+------------------------------------- Reporter: dylex | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: fixed | Keywords: 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.0.2 Comment: Indeed this appears to work with 8.0.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12473#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC