sifflet-lib-1.0: Library of modules shared by sifflet and its tests and its exporters.Source codeContentsIndex
Sifflet.Data.Tree
Synopsis
data Tree a = Node {
rootLabel :: a
subForest :: Forest a
}
tree :: e -> Forest e -> Tree e
leaf :: e -> Tree e
isLeaf :: Tree e -> Bool
treeSize :: Tree e -> Int
treeDepth :: Tree e -> Int
class Repr a where
repr :: a -> String
reprl :: a -> [String]
reprs :: a -> String
reprList :: String -> String -> String -> [a] -> String
data Name = Name String
nameTree :: Tree String -> Tree Name
putTree :: Show e => Tree e -> IO ()
putTreeR :: Repr e => Tree e -> IO ()
putTreeRs :: Repr e => Tree e -> IO ()
putTreeS :: Show e => Tree e -> IO ()
drawTreeShow :: Show e => Tree e -> String
Documentation
data Tree a Source
Multi-way trees, also known as rose trees.
Constructors
Node
rootLabel :: alabel value
subForest :: Forest azero or more child trees
show/hide Instances
tree :: e -> Forest e -> Tree eSource
leaf :: e -> Tree eSource
isLeaf :: Tree e -> BoolSource
treeSize :: Tree e -> IntSource
treeDepth :: Tree e -> IntSource
class Repr a whereSource

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 rest provide auxiliary information that you want to be shown with x. reprs x is a reduction of reprl x to a single String. reprList prefix infix postfix xs is the representation of a list of xs

Minimal complete implementation: define repr, or define reprl. The normal way is to define repr. Define reprl instead, if for some reason you want to include additional information such as the value of an expression in an expression node.

Examples: - (3 :: Int) has repr => 3, reprl => [3], reprs => 3 - In Sifflet.Language.Expr, (ENode (NSymbol x) (EvalOk (3 :: Int) has reprl => [x, 3], reprs => x 3, and repr => x. - reprList ( ) [3 :: Int, 4, 5] => (3 4 5)

Methods
repr :: a -> StringSource
reprl :: a -> [String]Source
reprs :: a -> StringSource
reprList :: String -> String -> String -> [a] -> StringSource
show/hide Instances
data Name Source
Constructors
Name String
show/hide Instances
nameTree :: Tree String -> Tree NameSource
putTree :: Show e => Tree e -> IO ()Source
putTreeR :: Repr e => Tree e -> IO ()Source
putTreeRs :: Repr e => Tree e -> IO ()Source
putTreeS :: Show e => Tree e -> IO ()Source
drawTreeShow :: Show e => Tree e -> StringSource
Produced by Haddock version 2.6.1