Bug? Or at least a better error message?

Geoffrey Alan Washburn geoffw at cis.upenn.edu
Sat Jun 3 13:46:53 EDT 2006


While trying out the following example, in an attempt to learn something 
about the fiddly case where a type class instance tries to use an 
instance that is more specific than itself

   module Testing where

   class Foo a where { bar :: a -> Int }

   instance Foo Int where
     bar i = i

   instance Foo a => Foo [a] where
     bar [] = bar [1]
     bar ([x]) = 1
     bar (x:xs) = (bar x) + (bar xs)

It is kind of like polymorphic recursion, I suppose.  I get the 
following exception

   [1 of 1] Compiling Testing          ( strange.hs, interpreted )
   *** Exception: typecheck/TcEnv.lhs:(365,0)-(392,32): Non-exhaustive
   patterns in function find_thing

Is the example supposed to work?  I'm trying to determine the source
of a problem with type classes and GADTs and I figured this example 
using "normal" data types would be a good place to start in 
understanding what was going wrong.

I was using ghci version 6.5.20060503.



More information about the Glasgow-haskell-users mailing list