[GHC] #9267: Lack of type information in GHC error messages when the liberage coverage condition is unsatisfied

GHC ghc-devs at haskell.org
Fri Jul 4 22:23:43 UTC 2014


#9267: Lack of type information in GHC error messages when the liberage coverage
condition is unsatisfied
-------------------------+-------------------------------------------------
       Reporter:         |             Owner:
  danilo2                |            Status:  new
           Type:  bug    |         Milestone:
       Priority:         |           Version:  7.8.2
  normal                 |  Operating System:  Unknown/Multiple
      Component:         |   Type of failure:  Incorrect warning at
  Compiler               |  compile-time
       Keywords:         |         Test Case:
   Architecture:         |          Blocking:
  Unknown/Multiple       |
     Difficulty:         |
  Unknown                |
     Blocked By:         |
Related Tickets:         |
-------------------------+-------------------------------------------------
 Hello! The problem is not a bug related to proper code execution, but it
 affects the development in such way, we can treat it as a bug.

 Lets think about such simple code (it can be further simplified of
 course):

   {{{#!haskell
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE UndecidableInstances #-}

 data UnsafeBase base err val = Value val
                              | Error err
                              | Other (base val)
                              deriving (Show, Eq)

 class MagicMerge m1 m2 | m1 -> m2 where
     magicMerge :: m1 a -> m2 a


 instance MagicMerge (UnsafeBase (UnsafeBase base err) err) (UnsafeBase
 base err) where
     magicMerge ma = case ma of
         Value a -> Value a
         Error e -> Error e
         Other o -> o

 instance MagicMerge (UnsafeBase (UnsafeBase base err1) err2) (UnsafeBase
 dstBase err1) where
     magicMerge (ma :: UnsafeBase (UnsafeBase base err1) err2 a) = case ma
 of
         Value a -> Value a
         Error e -> Other $ magicMerge (Error e :: UnsafeBase base err2 a)
         Other o -> case o of
             Value a  -> Other $ magicMerge (Value a  :: UnsafeBase base
 err2 a)
             Error e  -> Error e
             Other o' -> Other $ magicMerge (Other o' :: UnsafeBase base
 err2 a)


 main = print "help me world!"
   }}}

 When trying to compile it using GHC-7.8, we get following error message:

   {{{#!haskell
     Illegal instance declaration for
       ‘MagicMerge
          (UnsafeBase (UnsafeBase base err1) err2) (UnsafeBase dstBase
 err1)’
       The liberal coverage condition fails in class ‘MagicMerge’
         for functional dependency: ‘m1 -> m2’
       Reason: lhs type ‘UnsafeBase (UnsafeBase base err1) err2’
         does not determine rhs type ‘UnsafeBase dstBase err1’
     In the instance declaration for
       ‘MagicMerge (UnsafeBase (UnsafeBase base err1) err2) (UnsafeBase
 dstBase err1)’
   }}}

 Which is of course right, but it is completely unhelpfull! When we run the
 same program against GHC-7.6, we get another message:

   {{{#!haskell
     No instance for (MagicMerge (UnsafeBase base err2) dstBase)
       arising from a use of `magicMerge'
     Possible fix:
       add an instance declaration for
       (MagicMerge (UnsafeBase base err2) dstBase)
     In the second argument of `($)', namely
       `magicMerge (Error e :: UnsafeBase base err2 a)'
     In the expression:
       Other $ magicMerge (Error e :: UnsafeBase base err2 a)
     In a case alternative:
         Error e -> Other $ magicMerge (Error e :: UnsafeBase base err2 a)
   }}}

 And it contains a very helpfull information about inferred types. The
 information is very helpfull, especialy with more complex instances.

 What is VERY IMPORTANT, when we use the inferred type, the code starts
 working in both, GHC-7.8 and GHC-7.6. Right now I have to use both
 versions of GHC to be able to develop my instances faster.

 So If we add the inferred by GHC-7.6 premise:

   {{{#!haskell
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE UndecidableInstances #-}

 data UnsafeBase base err val = Value val
                              | Error err
                              | Other (base val)
                              deriving (Show, Eq)

 class MagicMerge m1 m2 | m1 -> m2 where
     magicMerge :: m1 a -> m2 a


 instance MagicMerge (UnsafeBase (UnsafeBase base err) err) (UnsafeBase
 base err) where
     magicMerge ma = case ma of
         Value a -> Value a
         Error e -> Error e
         Other o -> o

 instance (MagicMerge (UnsafeBase base err2) dstBase) => MagicMerge
 (UnsafeBase (UnsafeBase base err1) err2) (UnsafeBase dstBase err1) where
     magicMerge (ma :: UnsafeBase (UnsafeBase base err1) err2 a) = case ma
 of
         Value a -> Value a
         Error e -> Other $ magicMerge (Error e :: UnsafeBase base err2 a)
         Other o -> case o of
             Value a  -> Other $ magicMerge (Value a  :: UnsafeBase base
 err2 a)
             Error e  -> Error e
             Other o' -> Other $ magicMerge (Other o' :: UnsafeBase base
 err2 a)


 main = print "help me world!"
   }}}

 The code compiles and works ok in both GHC-7.6 and GHC-7.8. In such cases,
 GHC-7.8 should inform about lacking premises.

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


More information about the ghc-tickets mailing list