[GHC] #13902: Misleading function arity mismatch error with TypeApplications

#13902: Misleading function arity mismatch error with TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple TypeApplications | Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TypeApplications #-} f :: a -> a f x = x g :: Int g = f @Int 42 5 }}} {{{ GHCi, version 8.3.20170614: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:7:5: error: • Couldn't match expected type ‘Integer -> Int’ with actual type ‘Int’ • The function ‘f’ is applied to three arguments, but its type ‘Int -> Int’ has only one In the expression: f @Int 42 5 In an equation for ‘g’: g = f @Int 42 5 | 7 | g = f @Int 42 5 | ^^^^^^^^^^^ }}} That error message is quite confusing to read, since it reports that: * `f` is applied to three arguments, which //includes// a visible type application * `f` only has one argument, which //excludes// the visible type application We ought to be able to do better. My suggestion would be to report this instead: {{{ • The function ‘f @Int’ is applied to two arguments, but its type ‘Int -> Int’ has only one In the expression: f @Int 42 5 In an equation for ‘g’: g = f @Int 42 5 }}} Although I'm sure there are other ways the same information could be conveyed (e.g., `The function ‘f’ is applied to two value arguments`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13902 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13902: Misleading function arity mismatch error with TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I like treating the function and visible type application as a whole. The type of `f @Int` is `Int -> Int` and takes a single argument but that is not the type of `f` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13902#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13902: Misleading function arity mismatch error with TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto):
We ought to be able to do better.\\ Yes and it's good to share ideas.\\ I'd like to make a suggestion. It is not worth writing
{{{ In the expression: f @Int 42 5 In an equation for ‘g’: g = f @Int 42 5 }}} Since the compiler already indicates the place that has the expression and equation.\\ {{{ | 7 | g = f @Int 42 5 | ^^^^^^^^^^^ }}} Both sentences make redundancy and does not serve better to explain. Too much explanation is detrimental to the explanation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13902#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13902: Misleading function arity mismatch error with TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by RyanGlScott: Old description:
{{{#!hs {-# LANGUAGE TypeApplications #-}
f :: a -> a f x = x
g :: Int g = f @Int 42 5 }}} {{{ GHCi, version 8.3.20170614: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted )
Bug.hs:7:5: error: • Couldn't match expected type ‘Integer -> Int’ with actual type ‘Int’ • The function ‘f’ is applied to three arguments, but its type ‘Int -> Int’ has only one In the expression: f @Int 42 5 In an equation for ‘g’: g = f @Int 42 5 | 7 | g = f @Int 42 5 | ^^^^^^^^^^^ }}}
That error message is quite confusing to read, since it reports that:
* `f` is applied to three arguments, which //includes// a visible type application * `f` only has one argument, which //excludes// the visible type application
We ought to be able to do better. My suggestion would be to report this instead:
{{{ • The function ‘f @Int’ is applied to two arguments, but its type ‘Int -> Int’ has only one In the expression: f @Int 42 5 In an equation for ‘g’: g = f @Int 42 5 }}}
Although I'm sure there are other ways the same information could be conveyed (e.g., `The function ‘f’ is applied to two value arguments`).
New description: {{{#!hs {-# LANGUAGE TypeApplications #-} f :: a -> a f x = x g :: Int g = f @Int 42 5 }}} {{{ GHCi, version 8.3.20170614: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:7:5: error: • Couldn't match expected type ‘Integer -> Int’ with actual type ‘Int’ • The function ‘f’ is applied to three arguments, but its type ‘Int -> Int’ has only one In the expression: f @Int 42 5 In an equation for ‘g’: g = f @Int 42 5 | 7 | g = f @Int 42 5 | ^^^^^^^^^^^ }}} That error message is quite confusing to read, since it reports that: * `f` is applied to three arguments, which //includes// a visible type application * `f` only has one argument, which //excludes// the visible type application We ought to be able to do better. My suggestion would be to report this instead: {{{ • The expression ‘f @Int’ is applied to two arguments, but its type ‘Int -> Int’ has only one In the expression: f @Int 42 5 In an equation for ‘g’: g = f @Int 42 5 }}} Although I'm sure there are other ways the same information could be conveyed (e.g., `The function ‘f’ is applied to two value arguments`). -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13902#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13902: Misleading function arity mismatch error with TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3868 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3868 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13902#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13902: Misleading function arity mismatch error with TypeApplications
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.0.1
checker) | Keywords:
Resolution: | TypeApplications
Operating System: Unknown/Multiple | Architecture:
Type of failure: Poor/confusing | Unknown/Multiple
error message | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3868
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#13902: Misleading function arity mismatch error with TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: fixed | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Poor/confusing | Test Case: error message | typecheck/should_fail/T13902 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3868 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => typecheck/should_fail/T13902 * status: patch => closed * resolution: => fixed * milestone: => 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13902#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC