[Haskell-cafe] Ambiguous type variable

Arjun Guha guhaarju at grinnell.edu
Mon Jul 26 03:12:51 EDT 2004


Hi,

I'm new to Haskell and am getting this error:

AlphaBeta.hs:1:
     Ambiguous type variable `v' in the top-level constraint:
       `Ord v' arising from use of `maxValue' at AlphaBeta.hs:12

  in the following code:


module AlphaBeta where

-- Game states are instances of MinimaxState
class MinimaxState st where
   successors:: st -> [(action,st)]
   terminal:: st -> Bool
   utility:: (Ord v) => st -> v

minimaxDecision state =
   filter (\(_,st) -> utility st == v) (successors state)
   where
     v = maxValue state
     maxValue:: (MinimaxState state, Ord v) => state -> v
     maxValue state =
      if terminal state
        then utility state
        else (foldl max x xs)
          where (x:xs) = map (minValue.snd) (successors state)
     minValue:: (MinimaxState state, Ord v) => state -> v
     minValue state =
       if terminal state
         then utility state
         else (foldl min x xs)
           where (x:xs) = map (maxValue.snd) (successors state)


Any hints would be appreciated.

-Arjun



More information about the Haskell-Cafe mailing list