Ambiguous types

Daniel . constantine@soon.com
Mon, 21 Jan 2002 06:35:22 +0800


Hi there,
I've just starting learning Haskell and, to 
be quite frank, it gives me a cold sweat at 
times.

What has me confused at present is why the 
following code gives me :-
ActorTest.hs:8:
    Ambiguous type variable(s) `a' in the 
constraint `Action a'
    arising from use of `validActions' at 
ActorTest.hs:8
    In the first argument of `(==)', namely 
`validActions actor'
    In the definition of `canAct': 
(validActions actor) == []


{-code-}
module ActorTest where

class Actor t where

  canAct :: t -> Bool
  validActions :: (Action u) => t -> [u]

  canAct actor = validActions actor == []
  validActions actor = []

class Eq t => Action t
{-end code-}


Is the error saying that it is impossible to 
tell what specific type instance of the 
Action class will be returned by validActions?
If so, why should it matter?  Isn't it enough 
to know that they results will be of the 
class Action?

Thanks
Daniel

-- 

_______________________________________________
Sign-up for your own FREE Personalized E-mail at Mail.com
http://www.mail.com/?sr=signup


1 cent a minute calls anywhere in the U.S.!

http://www.getpennytalk.com/cgi-bin/adforward.cgi?p_key=RG9853KJ&url=http://www.getpennytalk.com