[GHC] #14319: Stuck kind families can lead to lousy error messages

GHC ghc-devs at haskell.org
Wed Oct 4 16:54:22 UTC 2017


#14319: Stuck kind families can lead to lousy error messages
-------------------------------------+-------------------------------------
           Reporter:  dfeuer         |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.4.1
          Component:  Compiler       |           Version:  8.3
  (Type checker)                     |
           Keywords:  TypeInType,    |  Operating System:  Unknown/Multiple
  TypeFamilies                       |
       Architecture:                 |   Type of failure:  Poor/confusing
  Unknown/Multiple                   |  error message
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{#!hs
 {-# language TypeFamilies, TypeInType, ScopedTypeVariables #-}

 module ArityError where
 import Data.Kind
 import GHC.TypeLits
 import Data.Proxy

 type family F (s :: Symbol) :: Type
 type family G (s :: Symbol) :: F s
 type instance G "Hi" = Maybe
 }}}

 This produces the error message

 {{{#!hs
 ArityError.hs:10:24: error:
     • Expecting one more argument to ‘Maybe’
       Expected kind ‘F "Hi"’, but ‘Maybe’ has kind ‘* -> *’
     • In the type ‘Maybe’
       In the type instance declaration for ‘G’
    |
 10 | type instance G "Hi" = Maybe
    |                        ^^^^^
 }}}

 This looks utterly bogus: `F "Hi"` is stuck, so we have no idea what arity
 it indicates. What I ''think'' is a term level version of this,

 {{{#!hs
 f :: forall (s :: Symbol). Proxy s -> F s
 f _ = Just
 }}}

 gives a much less confusing message:

 {{{
 ArityError.hs:14:7: error:
     • Couldn't match expected type ‘F s’
                   with actual type ‘a0 -> Maybe a0’
       The type variable ‘a0’ is ambiguous
     • In the expression: Just
       In an equation for ‘f’: f _ = Just
     • Relevant bindings include
         f :: Proxy s -> F s (bound at ArityError.hs:14:1)
    |
 14 | f _ = Just
    |       ^^^^
 }}}

 The fix (I think) is to refrain from reporting arity errors when we don't
 know enough about the relevant arities.

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


More information about the ghc-tickets mailing list