{- | Test functions for tree generation (should no more be in an output file ...) -} module Output( graphviz , viewName , opml ) where import Data.Tree(drawTree,Tree(..)) import Types import Data.List.Split import Test.QuickCheck import ViewServer(mkTree) import OPML import Graphviz randomTree :: Arbitrary a => Int -> Gen (Tree a) randomTree level | level == 0 = do a <- arbitrary return $ Node a [] | otherwise = do a <- arbitrary nb <- choose (1,5) children <- sequence (replicate nb (randomTree (level-1))) return $ Node a children instance Arbitrary a => Arbitrary (Tree a) where arbitrary = do level <- choose (1,4) randomTree level newtype Name = N String deriving(Eq,Show) toString (N s) = s instance Arbitrary Name where arbitrary = do n <- choose (1,5) let c = choose ('a','z') r <- sequence (replicate n c) return (N r) reconstruct_prop :: Tree Name -> Bool reconstruct_prop a = mkTree (flattenTree 0 a) == a flattenTree nb (Node a l) = (nb,a):concatMap (flattenTree (nb+1)) (reverse l)