[GHC] #12093: Wrong argument count in error message with TypeApplications

GHC ghc-devs at haskell.org
Fri May 20 16:09:01 UTC 2016


#12093: Wrong argument count in error message with TypeApplications
-------------------------------------+-------------------------------------
           Reporter:  kwf            |             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:  Incorrect
  Unknown/Multiple                   |  warning at compile-time
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 When I write:

 {{{#!hs
 {-# language TypeApplications #-}

 module Bug where

 wrong = id @Bool True False
 }}}

 I get the error:

 {{{
     • Couldn't match expected type ‘Bool -> t’ with actual type ‘Bool’
     • The function ‘id’ is applied to three arguments,
       but its type ‘Bool -> Bool’ has only one
       In the expression: id @Bool True False
       In an equation for ‘bad’: bad = id @Bool True False
     • Relevant bindings include bad :: t (bound at Bug.hs:8:1)
 }}}

 This seems to tell me that I ought to get rid of //two// of the arguments
 given to `id`, when in fact I only ought to remove //one//. In particular,
 the issue seems to be that GHC includes visibly applied type parameters in
 the count of "how many arguments is it applied to?" but does not include
 them in the count of "how many arguments does it have?"

 Suggested fix: in cases of this error with visible type application,
 report something akin to, "The function ‘id’ is applied to two type
 arguments and two value arguments, but its type has only one value
 argument."

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12093>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list