[GHC] #12393: Poor error message with equational type constraints

GHC ghc-devs at haskell.org
Thu Jul 14 14:04:00 UTC 2016


#12393: Poor error message with equational type constraints
--------------------------------------+---------------------------------
           Reporter:  laneb           |             Owner:
               Type:  bug             |            Status:  new
           Priority:  normal          |         Milestone:
          Component:  Compiler        |           Version:  8.0.1
           Keywords:                  |  Operating System:  Linux
       Architecture:  x86_64 (amd64)  |   Type of failure:  None/Unknown
          Test Case:                  |        Blocked By:
           Blocking:                  |   Related Tickets:
Differential Rev(s):                  |         Wiki Page:
--------------------------------------+---------------------------------
 GHCi 8.0.1 is giving a poor error message when it can't derive a typeclass
 when there's an equational type constraint involved.  A simple example:

 {{{#!hs
 {-# LANGUAGE TypeFamilies #-}

 class Foo a where
     type FooInner a
     fromInner :: FooInner a -> a

 newtype Bar = Bar { fromBar::Char } deriving (Show)
 instance Foo Bar where
     type FooInner Bar = Char
     fromInner = Bar

 myFunc :: (Foo foo, FooInner foo ~ Char) => String -> foo
 myFunc = fromInner . head
 }}}

 Many things work as expected:

 {{{
 ghc> :t myFunc
 myFunc :: (FooInner foo ~ Char, Foo foo) => String -> foo
 ghc> :t (myFunc "z")
 (myFunc "z") :: (FooInner foo ~ Char, Foo foo) => foo
 ghc> (myFunc "z") :: Bar
 Bar {fromBar = 'z'}
 }}}

 but if I just evaluate the function without the typecast I get an error:

 {{{
 ghc> myFunc "z"
 <interactive>:486:1: error:
     • Illegal equational constraint FooInner foo ~ Char
       (Use GADTs or TypeFamilies to permit this)
     • When checking the inferred type
         it :: forall foo. (FooInner foo ~ Char, Foo foo) => foo
 }}}

 Now, there should certainly be an error here: GHC doesn't know the exact
 type of {{{myFunc}}} so it can't check if it's an instance of {{{Show}}}.
 However, unless I'm not understanding what's going on, the error should be
 something like "Could not deduce Show", not "Illegal equational
 constraint".  Even if that __is__ what's going on, the suggestion to "Use
 GADTs or TypeFamilies to permit this" is clearly wrong, as I am already
 using {{{TypeFamilies}}}.

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


More information about the ghc-tickets mailing list