module Ideas.Common.Strategy.Choice
(
Choice(..)
, Menu, (|->), doneMenu, eqMenuBy
, elems, bests, bestsOrdered
, isEmpty, hasDone, getByIndex, cut
, onMenu, onMenuWithIndex
) where
import Data.Maybe
infixr 3 .|., ./., |>, :|:, :/:, :|>
infixr 5 |->, :->
class Choice a where
empty :: a
(.|.) :: a -> a -> a
(./.) :: a -> a -> a
(|>) :: a -> a -> a
choice :: [a] -> a
preference :: [a] -> a
orelse :: [a] -> a
choice xs = if null xs then empty else foldr1 (.|.) xs
preference xs = if null xs then empty else foldr1 (./.) xs
orelse xs = if null xs then empty else foldr1 (|>) xs
instance Choice [a] where
empty = []
(.|.) = (++)
(./.) = (++)
xs |> ys = if null xs then ys else xs
choice = concat
instance Choice b => Choice (a -> b) where
empty = const empty
(f .|. g) a = f a .|. g a
(f ./. g) a = f a ./. g a
(f |> g) a = f a |> g a
data Menu k a = k :-> a
| Done
| Empty
| Menu k a :|: Menu k a
| Menu k a :/: Menu k a
| Menu k a :|> Menu k a
instance (Eq k, Eq a) => Eq (Menu k a) where
(==) = eqMenuBy (==) (==)
instance Choice (Menu k a) where
empty = Empty
p0 .|. rest = rec p0
where
rec Empty = rest
rec (p :|: q) = p :|: rec q
rec p = case rest of
Empty -> p
_ -> p :|: rest
p0 ./. rest = rec p0
where
rec Empty = rest
rec (p :/: q) = p :/: rec q
rec p = p :/: rest
p0 |> rest = rec p0
where
rec Empty = rest
rec (p :|> q) = p :|> rec q
rec p = p :|> rest
instance Functor (Menu k) where
fmap f = rec
where
rec (p :|: q) = rec p :|: rec q
rec (p :/: q) = rec p :/: rec q
rec (p :|> q) = rec p :|> rec q
rec (k :-> a) = k :-> f a
rec Done = Done
rec Empty = Empty
(|->) :: a -> s -> Menu a s
(|->) = (:->)
doneMenu :: Menu k a
doneMenu = Done
hasDone :: Menu k a -> Bool
hasDone (p :|: q) = hasDone p || hasDone q
hasDone (p :/: q) = hasDone p || hasDone q
hasDone (p :|> _) = hasDone p
hasDone (_ :-> _) = False
hasDone Done = True
hasDone Empty = False
eqMenuBy :: (k -> k -> Bool) -> (a -> a -> Bool) -> Menu k a -> Menu k a -> Bool
eqMenuBy eqK eqA = test
where
test (p1 :|: p2) (q1 :|: q2) = test p1 q1 && test p2 q2
test (p1 :/: p2) (q1 :/: q2) = test p1 q1 && test p2 q2
test (p1 :|> p2) (q1 :|> q2) = test p1 q1 && test p2 q2
test (k1 :-> a1) (k2 :-> a2) = eqK k1 k2 && eqA a1 a2
test Done Done = True
test Empty Empty = True
test (p :/: Empty) q = test p q
test (p :|> Empty) q = test p q
test p (q :/: Empty) = test p q
test p (q :|> Empty) = test p q
test _ _ = False
elems :: Menu k a -> [(k, a)]
elems = ($ []) . rec
where
rec (p :|: q) = rec p . rec q
rec (p :/: q) = rec p . rec q
rec (p :|> q) = rec p . rec q
rec (k :-> a) = ((k, a):)
rec Done = id
rec Empty = id
bests :: Menu k a -> [(k, a)]
bests = bestsWith (++)
bestsOrdered :: (k -> k -> Ordering) -> Menu k a -> [(k, a)]
bestsOrdered cmp = bestsWith merge
where
merge lx@(x:xs) ly@(y:ys) =
case cmp (fst x) (fst y) of
GT -> y : merge lx ys
_ -> x : merge xs ly
merge [] ys = ys
merge xs [] = xs
bestsWith:: ([(k, a)] -> [(k, a)] -> [(k, a)]) -> Menu k a -> [(k, a)]
bestsWith f = rec
where
rec (p :|: q) = f (rec p) (rec q)
rec (p :/: q) = rec p ++ rec q
rec (p :|> _) = rec p
rec (k :-> a) = [(k, a)]
rec Done = []
rec Empty = []
isEmpty :: Menu k a -> Bool
isEmpty Empty = True
isEmpty _ = False
getByIndex :: Int -> Menu k a -> Maybe (k, a)
getByIndex n = listToMaybe . drop n . elems
cut :: Menu k a -> Menu k a
cut (p :|: q) = cut p .|. cut q
cut (p :/: q) = cut p ./. cut q
cut (p :|> _) = cut p
cut (k :-> a) = k |-> a
cut Done = doneMenu
cut Empty = empty
onMenu :: Choice b => (k -> a -> b) -> b -> Menu k a -> b
onMenu f e = rec
where
rec (p :|: q) = rec p .|. rec q
rec (p :/: q) = rec p ./. rec q
rec (p :|> q) = rec p |> rec q
rec (k :-> a) = f k a
rec Done = e
rec Empty = empty
onMenuWithIndex :: Choice b => (Int -> k -> a -> b) -> b -> Menu k a -> b
onMenuWithIndex f e = snd . rec 0
where
rec n (p :|: q) = let (n1, pn) = rec n p
(n2, qn) = rec n1 q
in (n2, pn .|. qn)
rec n (p :/: q) = let (n1, pn) = rec n p
(n2, qn) = rec n1 q
in (n2, pn ./. qn)
rec n (p :|> q) = let (n1, pn) = rec n p
(n2, qn) = rec n1 q
in (n2, pn |> qn)
rec n (k :-> a) = (n+1, f n k a)
rec n Done = (n, e)
rec n Empty = (n, empty)