module Ideas.Common.Strategy.Choice
(
Choice(..)
, Menu, eqMenuBy
, elems, bests, bestsOrdered, isEmpty, getByIndex
, onMenu, cut, cutOn, mapWithIndex
) where
import Data.Maybe (listToMaybe)
infixr 3 <|>, >|>, |>, :|:, :>|, :|>
class Choice f where
empty :: f a
single :: a -> f a
(<|>) :: f a -> f a -> f a
(>|>) :: f a -> f a -> f a
(|>) :: f a -> f a -> f a
oneof :: [a] -> f a
choice :: [f a] -> f a
oneof = choice . map single
choice xs
| null xs = empty
| otherwise = foldr1 (<|>) xs
instance Choice [] where
empty = []
single = return
(<|>) = (++)
(>|>) = (++)
xs |> ys = if null xs then ys else xs
oneof = id
choice = concat
data Menu a = Single a
| Empty
| Menu a :|: Menu a
| Menu a :>| Menu a
| Menu a :|> Menu a
instance Eq a => Eq (Menu a) where
(==) = eqMenuBy (==)
instance Choice Menu where
empty = Empty
single = Single
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 where
fmap f p = p >>= (Single . f)
instance Monad Menu where
return = single
fail _ = empty
(>>=) = flip onMenu
eqMenuBy :: (a -> a -> Bool) -> Menu a -> Menu a -> Bool
eqMenuBy eq = 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 (Single a) (Single b) = eq a b
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 a -> [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 (Single p) = (p:)
rec Empty = id
bests :: Menu a -> [a]
bests (p :|: q) = bests p ++ bests q
bests (p :>| q) = bests p ++ bests q
bests (p :|> q) = bests p |> bests q
bests (Single a) = [a]
bests Empty = []
bestsOrdered :: (a -> a -> Ordering) -> Menu a -> [a]
bestsOrdered cmp = rec
where
rec (p :|: q) = merge (rec p) (rec q)
rec (p :>| q) = rec p ++ rec q
rec (p :|> q) = rec p |> rec q
rec (Single a) = [a]
rec Empty = []
merge lx@(x:xs) ly@(y:ys)
| cmp x y == GT = y : merge lx ys
| otherwise = x : merge xs ly
merge [] ys = ys
merge xs [] = xs
isEmpty :: Menu a -> Bool
isEmpty Empty = True
isEmpty _ = False
getByIndex :: Int -> Menu a -> Maybe a
getByIndex n = listToMaybe . drop n . elems
onMenu :: Choice f => (a -> f b) -> Menu a -> f b
onMenu 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 (Single a) = f a
rec Empty = empty
cut :: Choice f => Menu a -> f a
cut (p :|: q) = cut p <|> cut q
cut (p :>| q) = cut p >|> cut q
cut (p :|> _) = cut p
cut (Single a) = single a
cut Empty = empty
cutOn :: Choice f => (a -> Bool) -> Menu a -> f a
cutOn f = snd . rec
where
rec (p :|: q) = let (b1, cp) = rec p
(b2, cq) = rec q
in (b1 || b2, cp <|> cq)
rec (p :>| q) = let (b1, cp) = rec p
(b2, cq) = rec q
in (b1 || b2, cp >|> cq)
rec (p :|> q) = let (b1, cp) = rec p
(b2, cq) = rec q
in (b1 || b2, if b1 then cp else cp |> cq)
rec (Single a) = (f a, single a)
rec Empty = (False, empty)
mapWithIndex :: Choice f => (Int -> a -> f b) -> Menu a -> f b
mapWithIndex f = 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 (Single a) = (n+1, f n a)
rec n Empty = (n, empty)