-- -- Type class for traversing AI game trees -- auxiliary definitions for labeling with static valuations -- module AI.Gametree where -- | a type class for gametrees -- parametrized by node type class Gametree p where children :: p -> [p] -- list of move, position is_terminal :: p -> Bool is_terminal = null . children -- default definition -- | type for valuation functions type Valuation a = a -> Int -- | a pair of something with a strict integer valuation -- supporting equality, ordering and limited arithmetic on valuation data Valued a = Valued { value :: !Int, unvalued :: a } deriving Show instance Functor Valued where fmap f (Valued v x) = Valued v (f x) -- | apply a valuation valued :: Valuation a -> a -> Valued a valued f x = Valued (f x) x -- | modify the valuation revalue :: (Int -> Int) -> Valued a -> Valued a revalue f (Valued v x) = Valued (f v) x instance Eq (Valued a) where x == y = value x==value y instance Ord (Valued a) where compare x y = compare (value x) (value y) -- some instances of numeric type class (only negate and fromInteger) instance Num (Valued a) where (+) = undefined (-) = undefined (*) = undefined negate = revalue negate fromInteger n = valued (const (fromIntegral n)) undefined abs = undefined signum = undefined -- | add a constant to a value infix 6 $+ ($+) :: Int -> Valued a -> Valued a k $+ x = revalue (+k) x