[GHC] #9612: Use functional dependencies to give more specific error messages

#9612: Use functional dependencies to give more specific error messages -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.3 checker) | Operating System: Keywords: | Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: Difficulty: Unknown | None/Unknown Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- An example from http://www.reddit.com/r/haskell/comments/2gryy8/stdlib_monad_error_messages_...: {{{#!hs f ::(Eq a) => a -> (Int, a) -> Writer [(Int, a)] (Int, a) f y (n,x) | y == x = return (n+1, x) | otherwise = do tell (n,x) return (1,y) }}} {{{ Could not deduce (MonadWriter (Int, a) (WriterT [(Int, a)] Data.Functor.Identity.Identity)) arising from a use of ‘tell’ from the context (Eq a) bound by the type signature for f :: Eq a => a -> (Int, a) -> Writer [(Int, a)] (Int, a) at 180.hs:42:5-57 In a stmt of a 'do' block: tell (n, x) In the expression: do { tell (n, x); return (1, y) } In an equation for ‘f’: f y (n, x) | y == x = return (n + 1, x) | otherwise = do { tell (n, x); return (1, y) } }}} GHC could realize that the class `MonadWriter m w` has a functional dependency `w -> m` and notice that there is an instance `MonadWriter w (WriterT w m1)` whose `m`-part unifies with that of the needed constraint. Therefore the error cannot be a missing instance, and GHC could give a more friendly error message like {{{ Couldn't match expected type `[(Int, a)]' with actual type `(Int, a)' when unifying the instance `MonadWriter w (WriterT w m1)' with the constraint `MonadWriter (Int, a) (WriterT [(Int, a)] Identity)' arising from a use of 'tell' In a stmt of a 'do' block: tell (n, x) In the expression: ... }}} (Or, if necessary, `Could not deduce [(Int, a)] ~ (Int, a) from the context (Eq a) ...`) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9612 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9612: Use functional dependencies to give more specific error messages -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Keywords: (Type checker) | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: Type of failure: | None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): Which version of GHC are you using? With HEAD or 7.8 I get {{{ T9612.hs:6:33: Couldn't match expected type ‘[(Int, a)]’ with actual type ‘(Int, a)’ Relevant bindings include x :: a (bound at T9612.hs:5:8) y :: a (bound at T9612.hs:5:3) f :: a -> (Int, a) -> Writer [(Int, a)] (Int, a) (bound at T9612.hs:5:1) In the first argument of ‘tell’, namely ‘(n, x)’ In a stmt of a 'do' block: tell (n, x) }}} which is certainly better than the one you display. I had to add `import Control.Monad.Trans.Writer.Strict` at the top. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9612#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9612: Use functional dependencies to give more specific error messages -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Keywords: (Type checker) | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: Type of failure: | None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by rwbarton): Oh, I meant for `tell` to be the one from mtl `Control.Monad.Writer`, sorry. {{{ class (Monoid w, Monad m) => MonadWriter w m | m -> w where writer :: (a,w) -> m a tell :: w -> m () listen :: m a -> m (a, w) pass :: m (a, w -> w) -> m a }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9612#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9612: Use functional dependencies to give more specific error messages
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner:
Type: feature | Status: new
request | Milestone:
Priority: normal | Version: 7.8.3
Component: Compiler | Keywords:
(Type checker) | Architecture: Unknown/Multiple
Resolution: | Difficulty: Unknown
Operating System: | Blocked By:
Unknown/Multiple | Related Tickets:
Type of failure: |
None/Unknown |
Test Case: |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#9612: Use functional dependencies to give more specific error messages
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner:
Type: feature | Status: new
request | Milestone:
Priority: normal | Version: 7.8.3
Component: Compiler | Keywords:
(Type checker) | Architecture: Unknown/Multiple
Resolution: | Difficulty: Unknown
Operating System: | Blocked By:
Unknown/Multiple | Related Tickets:
Type of failure: |
None/Unknown |
Test Case: |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#9612: Use functional dependencies to give more specific error messages -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: feature | Status: closed request | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Keywords: (Type checker) | Architecture: Unknown/Multiple Resolution: fixed | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: Type of failure: | None/Unknown | Test Case: | typecheck/should_fail/T9612 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => typecheck/should_fail/T9612 * resolution: => fixed Comment: Good idea, thank you. The error message is now {{{ T9612.hs:16:9: Couldn't match type ‘[(Int, a)]’ with ‘(Int, a)’ arising from a functional dependency between: constraint ‘MonadWriter (Int, a) (WriterT [(Int, a)] Identity)’ arising from a use of ‘tell’ instance ‘MonadWriter w (WriterT w m)’ at T9612.hs:20:10-59 }}} Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9612#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC