module Data.Forest.Static where
import Control.Applicative ((<$>),(<*>))
import Control.Monad (replicateM)
import Data.Foldable (toList)
import Data.Graph.Inductive.Basic
import Data.List (span,uncons,sort)
import Data.Traversable (mapAccumL)
import Data.Tree (Tree)
import Debug.Trace
import qualified Data.List as L
import qualified Data.Map.Strict as S
import qualified Data.Set as Set
import qualified Data.Tree as T
import qualified Data.Vector as V
import qualified Data.Vector.Generic as VG
import qualified Data.Vector.Unboxed as VU
import Test.QuickCheck
data TreeOrder = Pre | Post | Unordered
data Forest (p :: TreeOrder) v a where
Forest :: (VG.Vector v a) =>
{ label :: v a
, parent :: VU.Vector Int
, children :: V.Vector (VU.Vector Int)
, lsib :: VU.Vector Int
, rsib :: VU.Vector Int
, roots :: VU.Vector Int
} -> Forest p v a
deriving instance (Show a, Show (v a)) => Show (Forest p v a)
forestWith :: (VG.Vector v a) => (forall a . [T.Tree a] -> [a]) -> [T.Tree a] -> Forest (p::TreeOrder) v a
forestWith f ts
= Forest { label = VG.fromList $ f ts
, parent = VU.fromList $ map (\(_,k,_ ,_) -> k ) $ f pcs
, children = V.fromList $ map (\(_,_,cs,_) -> VU.fromList cs) $ f pcs
, lsib = VU.fromList $ map fst $ S.elems lr
, rsib = VU.fromList $ map snd $ S.elems lr
, roots = VU.fromList $ map (fst . T.rootLabel) us
}
where
ps = addIndicesF' 0 ts
backp = VU.fromList $ map snd $ sort $ zip (f ps) [0..]
us = map (fmap (\(k,l) -> (backp VG.! k,l))) $ addIndicesF 0 ts
pcs = parentChildrenF (-1) us
lr = lrSiblingF us
forestPre :: (VG.Vector v a) => [T.Tree a] -> Forest Pre v a
forestPre = forestWith preorderF
forestPost :: (VG.Vector v a) => [T.Tree a] -> Forest Post v a
forestPost = forestWith postorderF
addIndices :: Int -> T.Tree a -> T.Tree (Int,a)
addIndices k = snd . mapAccumL (\i e -> (i+1, (i,e))) k
addIndicesF :: Int -> [T.Tree a] -> [T.Tree (Int,a)]
addIndicesF k = snd . mapAccumL go k
where go = mapAccumL (\i e -> (i+1, (i,e)))
addIndicesF' :: Int -> [T.Tree a] -> [T.Tree Int]
addIndicesF' k = snd . mapAccumL go k
where go = mapAccumL (\i e -> (i+1, i))
parentChildrenF :: Int -> [T.Tree (Int,a)] -> [T.Tree (Int,Int,[Int],a)]
parentChildrenF k ts = [ T.Node (i,k,children sf,l) (parentChildrenF i sf) | T.Node (i,l) sf <- ts ]
where children sf = map (fst . T.rootLabel) sf
lrSiblingF :: [T.Tree (Int,a)] -> S.Map Int (Int,Int)
lrSiblingF = S.delete (-1) . lrSibling . T.Node (-1,error "laziness in lrSiblingF broken")
lrSibling :: T.Tree (Int,a) -> S.Map Int (Int,Int)
lrSibling = S.fromList . map splt . T.flatten . go ([]::[Int])
where go sib (T.Node (k,lbl) frst) = let cs = [l | T.Node (l,_) _ <- frst] in T.Node (k,lbl,sib) [ go cs t | t <- frst]
splt (k,_,[]) = (k,(-1,-1))
splt (k,_,sbl) = let (ls,rs) = span (/=k) sbl in (k,(last $ (-1):ls,head $ tail rs ++ [-1]))
leftMostLeaves :: Forest p v a -> VU.Vector Int
leftMostLeaves f = VG.map (leftMostLeaf f) $ VG.enumFromN 0 $ VG.length $ parent f
leftMostLeaf :: Forest p v a -> Int -> Int
leftMostLeaf f = go
where go k = let cs = children f VG.! k
in if VG.null cs then k else go (VG.head cs)
rightMostLeaves :: Forest p v a -> VU.Vector Int
rightMostLeaves f = VG.map (rightMostLeaf f) $ VG.enumFromN 0 $ VG.length $ parent f
rightMostLeaf :: Forest p v a -> Int -> Int
rightMostLeaf f = go
where go k = let cs = children f VG.! k
in if VG.null cs then k else go (VG.last cs)
leftKeyRoots :: Forest Post v a -> VU.Vector Int
leftKeyRoots f = VU.fromList . sort . S.elems $ VU.foldl' go S.empty (VU.enumFromN (0::Int) $ VG.length $ parent f)
where go s k = S.insertWith max (lml VU.! k) k s
lml = leftMostLeaves f
sortedSubForests :: Forest p v a -> [VU.Vector Int]
sortedSubForests f =
map VU.fromList
. L.nub
. concat
. map (map unSrt . Set.toList . Set.fromList . map Srt)
. map (concatMap (L.tail . L.subsequences))
. map (L.permutations)
. map VG.toList . VG.toList
. VG.filter (not . VG.null)
$ VG.snoc (VG.reverse (children f)) (roots f)
newtype Srt = Srt { unSrt :: [Int] }
deriving (Eq,Show)
instance Ord Srt where
Srt xs <= Srt ys = length xs <= length ys
forestToTrees :: Forest p v a -> T.Forest a
forestToTrees Forest{..} = map getTree . VG.toList $ roots
where getTree k = T.Node (label VG.! k) (map getTree . VG.toList $ children VG.! k)
newtype QCTree a = QCTree { getTree :: T.Tree a }
deriving (Show)
instance (Arbitrary a) => Arbitrary (QCTree a) where
arbitrary =
let go = sized $ \n ->
do val <- arbitrary
let n' = n `div` 2
nodes <- if n' > 0
then do k <- choose (0,n')
resize n' $ replicateM k (getTree <$> arbitrary)
else return []
return $ T.Node val nodes
in QCTree <$> go
shrink (QCTree (T.Node val forest)) =
[]
test1 :: [T.Tree Char]
test1 = [T.Node 'R' [T.Node 'a' [], T.Node 'b' []], T.Node 'S' [T.Node 'x' [], T.Node 'y' []]]
test2 :: [T.Tree Char]
test2 = [T.Node 'R' [T.Node 'a' [], T.Node 'b' [], T.Node 'c' []]]
runtest t = do
print (forestPre t :: Forest Pre V.Vector Char)
print (forestPost t :: Forest Post V.Vector Char)
print (forestPost [T.Node 'R' [T.Node 'a' []]] :: Forest Post V.Vector Char)
print (forestPost [T.Node 'R' [T.Node 'a' [], T.Node 'b' []]] :: Forest Post V.Vector Char)
print (sortedSubForests (forestPre t :: Forest Pre V.Vector Char))