-- Tree.hs -- General (not binary) trees module Tree (T.Tree(..), tree, leaf, isLeaf, treeSize, treeDepth , Repr(..) -- Since String is not an instance of Repr, -- we need to convert (Tree String) to (Tree Name) , Name(..), nameTree , putTree, putTreeR, putTreeRs, putTreeS , drawTreeShow ) where import Data.Tree as T -- Makers tree :: e -> Forest e -> T.Tree e tree root subtrees = T.Node {rootLabel = root, subForest = subtrees} leaf :: e -> T.Tree e leaf x = tree x [] isLeaf :: T.Tree e -> Bool isLeaf (T.Node _root []) = True isLeaf _ = False treeSize :: T.Tree e -> Int treeSize (T.Node _root subtrees) = 1 + sum (map treeSize subtrees) treeDepth :: T.Tree e -> Int treeDepth (T.Node _root []) = 1 treeDepth (T.Node _root subtrees) = 1 + maximum (map treeDepth subtrees) {- tree_map or treeMap: removed; use (Functor) fmap instead -} {- tree_mapM: removed, use Data.Traversable.mapM instead. -} -- class Repr: representable by a String or a list of Strings -- repr x is a String representation of x. -- reprl x is a [String] representation of x, -- where the first element should be the same as repr x, -- and the extra values, if any, provide auxiliary information, -- such as the value of x. -- reprs x is a reduction of reprl x to a single String. -- -- Minimal complete implementation: define repr, or define reprl. class Repr a where repr :: a -> String repr = head . reprl reprl :: a -> [String] reprl x = [repr x] reprs :: a -> String reprs = unwords . reprl instance Repr Int where repr = show instance Repr Integer where repr = show instance Repr Float where repr = show instance Repr Double where repr = show -- instance Repr String won't work because String is a type synonym, -- unless you ask ghc nicely, which I'd prefer not to do. -- Use Name data type in Testing/Tree.hs instead, or Symbol in Expr.hs -- I don't know if I can use Expr.Symbol here, since Expr.hs also -- imports Tree.hs (this file) -- is mutual import allowed? data Name = Name String deriving (Eq, Read, Show) instance Repr Name where repr (Name s) = s nameTree :: T.Tree String -> T.Tree Name nameTree = fmap Name putTree :: (Show e) => T.Tree e -> IO () putTree = putTreeS -- putTreeR -- using repr (first part) putTreeR :: (Repr e) => T.Tree e -> IO() putTreeR = putStrLn . drawTree . fmap repr -- putTreeRs -- using reprs (all parts) putTreeRs :: (Repr e) => T.Tree e -> IO() putTreeRs = putStrLn . drawTree . fmap reprs -- putTreeS -- using show putTreeS :: (Show e) => T.Tree e -> IO () putTreeS = putStrLn . drawTreeShow drawTreeShow :: (Show e) => T.Tree e -> String drawTreeShow = drawTree . fmap show