module Ideas.Common.DerivationTree
(
DerivationTree
, singleNode, addBranches, makeTree
, root, endpoint, branches, subtrees
, leafs, lengthMax
, restrictHeight, restrictWidth, updateAnnotations
, cutOnStep, mergeMaybeSteps, sortTree, cutOnTerm
, derivation, randomDerivation, derivations
) where
import Control.Arrow
import Control.Monad
import Data.List
import Data.Maybe
import Ideas.Common.Classes
import Ideas.Common.Derivation
import System.Random
data DerivationTree s a = DT
{ root :: a
, endpoint :: Bool
, branches :: [(s, DerivationTree s a)]
}
deriving Show
instance Functor (DerivationTree s) where
fmap = mapSecond
instance BiFunctor DerivationTree where
biMap f g (DT a b xs) = DT (g a) b (map (biMap f (biMap f g)) xs)
singleNode :: a -> Bool -> DerivationTree s a
singleNode a b = DT a b []
addBranches :: [(s, DerivationTree s a)] -> DerivationTree s a -> DerivationTree s a
addBranches new (DT a b xs) = DT a b (xs ++ new)
makeTree :: (a -> (Bool, [(s, a)])) -> a -> DerivationTree s a
makeTree f = rec
where
rec a = let (b, xs) = f a
in addBranches (map (mapSecond rec) xs) (singleNode a b)
annotations :: DerivationTree s a -> [s]
annotations = map fst . branches
subtrees :: DerivationTree s a -> [DerivationTree s a]
subtrees = map snd . branches
leafs :: DerivationTree s a -> [a]
leafs t = [ root t | endpoint t ] ++ concatMap leafs (subtrees t)
lengthMax :: Int -> DerivationTree s a -> Maybe Int
lengthMax n = join . fmap (f . derivationLength) . derivation
. commit . restrictHeight (n+1)
where
f i = if i<=n then Just i else Nothing
updateAnnotations :: (a -> s -> a -> t) -> DerivationTree s a -> DerivationTree t a
updateAnnotations f = rec
where
rec (DT a b xs) =
let g (s, t) = (f a s (root t), rec t)
in DT a b (map g xs)
restrictHeight :: Int -> DerivationTree s a -> DerivationTree s a
restrictHeight n t
| n == 0 = singleNode (root t) True
| otherwise = t {branches = map f (branches t)}
where
f = mapSecond (restrictHeight (n1))
restrictWidth :: Int -> DerivationTree s a -> DerivationTree s a
restrictWidth n = rec
where
rec t = t {branches = map (mapSecond rec) (take n (branches t))}
commit :: DerivationTree s a -> DerivationTree s a
commit = restrictWidth 1
mergeSteps :: (s -> Bool) -> DerivationTree s a -> DerivationTree s a
mergeSteps p = rec
where
rec t = addBranches (concat list) (singleNode (root t) isEnd)
where
new = map rec (subtrees t)
(bools, list) = unzip (zipWith f (annotations t) new)
isEnd = endpoint t || or bools
f s st
| p s = (False, [(s, st)])
| otherwise = (endpoint st, branches st)
sortTree :: (l -> l -> Ordering) -> DerivationTree l a -> DerivationTree l a
sortTree f t = t {branches = change (branches t) }
where
change = map (mapSecond (sortTree f)) . sortBy cmp
cmp (l1, _) (l2, _) = f l1 l2
mergeMaybeSteps :: DerivationTree (Maybe s) a -> DerivationTree s a
mergeMaybeSteps = mapFirst fromJust . mergeSteps isJust
cutOnStep :: (s -> Bool) -> DerivationTree s a -> DerivationTree s a
cutOnStep p = rec
where
rec t = t {branches = map f (branches t)}
f (s, t)
| p s = (s, singleNode (root t) True)
| otherwise = (s, rec t)
cutOnTerm :: (a -> Bool) -> DerivationTree s a -> DerivationTree s a
cutOnTerm p (DT r e bs) =
DT r e (map (second (cutOnTerm p)) $ filter (not . p . root . snd) bs)
derivations :: DerivationTree s a -> [Derivation s a]
derivations t =
[ emptyDerivation (root t) | endpoint t ] ++
[ (root t, r) `prepend` d | (r, st) <- branches t, d <- derivations st ]
derivation :: DerivationTree s a -> Maybe (Derivation s a)
derivation = listToMaybe . derivations
randomDerivation :: RandomGen g => g -> DerivationTree s a -> Maybe (Derivation s a)
randomDerivation g t = msum xs
where
(xs, g0) = shuffle g list
list = [ Just (emptyDerivation (root t)) | endpoint t ] ++
map make (branches t)
make (r, st) = do
d <- randomDerivation g0 st
return ((root t, r) `prepend` d)
shuffle :: RandomGen g => g -> [a] -> ([a], g)
shuffle g0 xs = rec g0 [] (length xs) xs
where
rec g acc n ys =
case splitAt i ys of
(as, b:bs) -> rec g1 (b:acc) (n1) (as++bs)
_ -> (acc, g)
where
(i, g1) = randomR (0, n1) g