[GHC] #9650: Unsatisfiable default signature

#9650: Unsatisfiable default signature -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: GHC Blocked By: | accepts invalid program Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- I discovered the `-XDefaultSignatures` extension and promptly wrote a default method that I feel should be rejected by the compiler: {{{#!hs {-# LANGUAGE DefaultSignatures #-} module Foo where class Foo a where foo :: proxy a -> b -> Int default foo :: (Integral b) => proxy a -> b -> Int foo _ b = fromIntegral b }}} GHC accepts this code, but rejects the instance `instance Foo Bool` because `No instance for (Integral b) arising from a use of ‘Foo.$gdmfoo’`. It seems to me that the class should have never compiled in the first place. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9650 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9650: Unsatisfiable default signature -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: GHC | Blocked By: accepts invalid program | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: dreixel (added) Comment: You point is, I think, that constraints that constrain ''only'' `b` (in this example) cannot possibly be satisfied at the usage site. If you wrote {{{ class Foo a where foo :: ...blah.. default foo :: forall b. (C a b) => ...blah... foo = ... }}} then a suitable instance for `C` (e.g. `instance C Int b`) might allow the `C a b` constraint to be satisfied at the `instance` declaration. However, nothing stops you writing {{{ instance Integral b where ... }}} and now the constraint would be satisfied. You may say this is silly, but people do write instance declarations like this (often `OVERLAPPABLE`). So I think the most we could do would be to warn that the default signature looks fishy. And then people would want a way to suppress the warning.... In short, there is merit in what you say, but I don't see an obvious way to take advantage of your observation. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9650#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9650: Unsatisfiable default signature -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: GHC | Blocked By: accepts invalid program | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dreixel): I think there will always be examples of unsatisfiable defaults, and GHC can't, in general, spot them. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9650#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9650: Unsatisfiable default signature -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: invalid | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: GHC | Blocked By: accepts invalid program | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by crockeea): * status: new => closed * resolution: => invalid Comment: I see Simon's point, so I suppose there's nothing to be done here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9650#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC