You gave test a type signature which gives "a" universal quantification, which means in this case that "a" is something, but you can't do anything in particular to it (since you don't know anything about it).

shift has the signature a -> Int -> a, but it's within the type class Bits:

Prelude> import Data.Bits
Prelude Data.Bits> :i shift
class (Num a) => Bits a where
...
shift :: a -> Int -> a
...
        -- Defined in Data.Bits
infixl 8 shift

So in this case, "a" is actually the "a" from "Bits a" above. Your function, test, does not say that "a" is a bits, and that's what the compiler is telling you.

Change your type signature to

shift :: Bits a => a -> Int -> a

and it should be good to go!

-Ross

P.S. I'm something of a haskell newbie, so if I got any of this wrong, please someone more knowledgeable correct me!

On May 8, 2008, at 3:10 PM, Wei Yuan Cai wrote:
Hello,

I'm having some trouble with a polymorphic function using another polymorphic function within. A simplified code of what I'm trying to do is as follows:

main = print $ test 1 8

test :: a -> Int -> a
test x n = shift x n

I get the following compilation error:

Could not deduce (Data.Bits.Bits a) from the context ()
      arising from a use of `shift' at test.hs:8:11-19
    Possible fix:
      add (Data.Bits.Bits a) to the context of
        the type signature for `test'
    In the expression: shift x n
    In the definition of `test': test x n = shift x n


shift is defined as "a -> Int -> a"

What am I doing wrong here?

Thanks,
Weiyuan
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to