[GHC] #12587: InstanceSigs doesn't work with ambigous types

#12587: InstanceSigs doesn't work with ambigous types -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- Why this code: {{{#!hs {-# LANGUAGE ScopedTypeVariables, InstanceSigs, AllowAmbiguousTypes #-} module Bug where class Foo a class Bar a where bar :: forall b. (Foo b) => a instance Bar Int where bar :: forall b. (Foo b) => Int -- error here bar = undefined where x :: b x = undefined }}} is rejected with message: {{{ Error: * Could not deduce (Foo b0) from the context: Foo b bound by the type signature for: bar :: Foo b => Int at Bug.hs:11:12-35 The type variable `b0' is ambiguous * When checking that: forall b. Foo b => Int is more polymorphic than: forall b. Foo b => Int When checking that instance signature for `bar' is more general than its signature in the class Instance sig: forall b. Foo b => Int Class sig: forall b. Foo b => Int In the instance declaration for `Bar Int' }}} ? Where does `b0` type var come from? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12587 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12587: InstanceSigs doesn't work with ambigous types -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: invalid | 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 simonpj): * status: new => closed * resolution: => invalid Comment: In your instance decl (I have renamed the forall'd variable). {{{ instance Bar Int where bar :: forall c. (Foo c) => Int -- error here bar = undefined where x :: c x = undefined }}} GHC is trying to check that the instance signature you ''provide'': {{{ bar :: forall c. Foo c => Int }}} is more general than the one that is ''required'': {{{ bar :: forall b. Foo b => Int }}} To to that it * instantiates the required one, giving `[W] Foo b0` * unifies provided and requied types `Int ~ Int` * checks that it can prove the required `[W] Foo b0` from the given `Foo c`. But it can't prove that because nothing tells GHC to instantiate `b0` to `c`. I think this is fair enough: it really is an ambiguous type. The same thing would happen if you used an auxiliary function {{{ instance Bar Int where bar = barInt barInt :: forall c. (Foo c) => Int -- error here barInt = undefined where x :: c x = undefined }}} Indeed, it'd be surprising if this didn't work but the previous code did. So I think it's fine. Yell if you disagree. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12587#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC