[Haskell-cafe] is there something special about the Num instance?

Daniel Fischer daniel.is.fischer at web.de
Wed Dec 3 18:34:23 EST 2008


Am Donnerstag, 4. Dezember 2008 00:05 schrieb Anatoly Yakovenko:
> module Test where
> --why does this work:
> data Test = Test
>
> class Foo t where
>    foo :: Num v => t -> v -> IO ()
>
> instance Foo Test where
>    foo _ 1 = print $ "one"
>    foo _ _ = print $ "not one"
>
> --but this doesn't?
>
> class Bar t where
>    bar :: Foo v => t -> v -> IO ()
>
> instance Bar Test where
>    bar _ Test = print $ "test"
>    bar _ _ = print $ "not test"

Because bar has to work for all types which belong to 
class Foo, but actually uses the type Test.
This is what the error message

Test.hs:18:10:
    Couldn't match expected type `v' against inferred type `Test'
      `v' is a rigid type variable bound by
          the type signature for `bar' at Test.hs:15:15
    In the pattern: Test
    In the definition of `bar': bar _ Test = print $ "test"
    In the definition for method `bar'

tells you. In the signature of bar, you've said that bar works for all types v 
which are members of Foo. Test is a monomorphic value of type Test, so it 
can't have type v for all v which belong to Foo.

It doesn't matter that there is so far only the one instance of Foo, there 
could be others defined in other modules.

The first works because the type of 1 in the definition of foo is defaulted to 
Integer (or whatever you specified in the default declaration).




More information about the Haskell-Cafe mailing list