Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Configurable text rendering of trees.
Example renderings for:
import Data.Tree import Data.Tree.Render.Text tree :: Tree String tree = Node "Add" [ Node "Add" [ Node "0" [] , Node "Mul" [ Node "1" [] , Node "2" [] ] ] , Node "Neg" [ Node "Max" [ Node "3" [] , Node "4" [] , Node "5" [] , Node "Var" [ Node "x" [] ] , Node "6" [] ] ] ] renderTree (tracedRenderOptions id) tree ● Add ├─● Add │ ├─● 0 │ ╰─● Mul │ ├─● 1 │ ╰─● 2 ╰─● Neg ╰─● Max ├─● 3 ├─● 4 ├─● 5 ├─● Var │ ╰─● x ╰─● 6 Other renderings by setting 'ParentLocation' and 'ChildOrder' in the options: ╭─● 0 ╭─● 0 ● Add ╭─● 6 ╭─● 6 │ ╭─● 1 ╭─● Add ├─● Neg │ ╭─● x │ ╭─● x │ ├─● 2 │ │ ╭─● 1 │ ╰─● Max ├─● Var ├─● Var ├─● Mul │ ╰─● Mul │ ├─● 6 ├─● 5 ├─● 5 ╭─● Add │ ╰─● 2 │ ├─● Var ├─● 4 ╭─● Max │ ╭─● 3 ● Add │ │ ╰─● x ├─● 3 │ ├─● 4 │ ├─● 4 ╰─● Neg │ ├─● 5 ╭─● Max │ ╰─● 3 │ ├─● 5 │ ╭─● 3 │ ├─● 4 ╭─● Neg ╭─● Neg │ │ ╭─● x │ ├─● 4 │ ╰─● 3 │ ╭─● 2 ● Add │ ├─● Var ╰─● Max ╰─● Add │ ├─● 1 │ ╭─● 2 │ ├─● 6 ├─● 5 ├─● Mul │ ╭─● Mul │ ╭─● Mul │ ╭─● Max ├─● Var │ ├─● 2 │ ├─● 0 │ │ ╰─● 1 ├─● Neg │ ╰─● x │ ╰─● 1 ├─● Add ╰─● Add ● Add ╰─● 6 ╰─● 0 ● Add ╰─● 0
Synopsis
- data ParentLocation
- data ChildOrder
- data BranchPath
- data LocalContext label = LocalContext {
- lcCurrentNode :: Tree label
- lcCurrentDepth :: !Int
- lcLitterIndex :: !Int
- lcLitterSize :: !Int
- data RenderOptionsM m string label = RenderOptions {
- oParentLocation :: Maybe (LocalContext label) -> m ParentLocation
- oChildOrder :: Maybe (LocalContext label) -> m ChildOrder
- oVerticalPad :: Int
- oPrependNewline :: Bool
- oWriteNewline :: m ()
- oWrite :: string -> m ()
- oShowNodeLabel :: Maybe label -> m string
- oNodeMarker :: Maybe (LocalContext label) -> m string
- oShowBranchPath :: BranchPath -> string
- type RenderOptions = RenderOptionsM (Writer (DList Char))
- renderTree :: RenderOptions String label -> Tree label -> String
- renderForest :: RenderOptions String label -> Forest label -> String
- renderTreeM :: Monad m => RenderOptionsM m string label -> Tree label -> m ()
- renderForestM :: Monad m => RenderOptionsM m string label -> Forest label -> m ()
- tracedRenderOptions :: (label -> String) -> RenderOptions String label
- tracedRenderOptionsAscii :: (label -> String) -> RenderOptions String label
- middleCutRenderOptions :: (label -> String) -> RenderOptions String label
- zigZagRenderOptions :: (label -> String) -> RenderOptions String label
- tabbedRenderOptions :: String -> (label -> String) -> RenderOptions String label
- tracedRenderOptionsM :: Monad m => (String -> string) -> (string -> m ()) -> (label -> m string) -> RenderOptionsM m string label
- tracedRenderOptionsAsciiM :: Monad m => (String -> string) -> (string -> m ()) -> (label -> m string) -> RenderOptionsM m string label
- middleCutRenderOptionsM :: Monad m => (String -> string) -> (string -> m ()) -> (label -> m string) -> RenderOptionsM m string label
- zigZagRenderOptionsM :: Monad m => (String -> string) -> (string -> m ()) -> (label -> m string) -> RenderOptionsM m string label
- tabbedRenderOptionsM :: Monad m => String -> (String -> string) -> (string -> m ()) -> (label -> m string) -> RenderOptionsM m string label
Documentation
data ParentLocation Source #
Describes where a parent node is rendered, relative to its children.
ParentBeforeChildren | Renders the parent before any of its children. |
ParentAfterChildren | Renders the parent after all of its children. |
ParentBetweenChildren | Renders the parent in the middle of its children (if there are multiple children).
The index is rounded down when using |
ParentAtChildIndex Int | This is a value from A value of |
Instances
Eq ParentLocation Source # | |
Defined in Data.Tree.Render.Text (==) :: ParentLocation -> ParentLocation -> Bool # (/=) :: ParentLocation -> ParentLocation -> Bool # | |
Ord ParentLocation Source # | |
Defined in Data.Tree.Render.Text compare :: ParentLocation -> ParentLocation -> Ordering # (<) :: ParentLocation -> ParentLocation -> Bool # (<=) :: ParentLocation -> ParentLocation -> Bool # (>) :: ParentLocation -> ParentLocation -> Bool # (>=) :: ParentLocation -> ParentLocation -> Bool # max :: ParentLocation -> ParentLocation -> ParentLocation # min :: ParentLocation -> ParentLocation -> ParentLocation # | |
Show ParentLocation Source # | |
Defined in Data.Tree.Render.Text showsPrec :: Int -> ParentLocation -> ShowS # show :: ParentLocation -> String # showList :: [ParentLocation] -> ShowS # |
data ChildOrder Source #
Describes the render order of a node's children.
Instances
Eq ChildOrder Source # | |
Defined in Data.Tree.Render.Text (==) :: ChildOrder -> ChildOrder -> Bool # (/=) :: ChildOrder -> ChildOrder -> Bool # | |
Ord ChildOrder Source # | |
Defined in Data.Tree.Render.Text compare :: ChildOrder -> ChildOrder -> Ordering # (<) :: ChildOrder -> ChildOrder -> Bool # (<=) :: ChildOrder -> ChildOrder -> Bool # (>) :: ChildOrder -> ChildOrder -> Bool # (>=) :: ChildOrder -> ChildOrder -> Bool # max :: ChildOrder -> ChildOrder -> ChildOrder # min :: ChildOrder -> ChildOrder -> ChildOrder # | |
Show ChildOrder Source # | |
Defined in Data.Tree.Render.Text showsPrec :: Int -> ChildOrder -> ShowS # show :: ChildOrder -> String # showList :: [ChildOrder] -> ShowS # |
data BranchPath Source #
A part of a path along a rendered tree.
BranchUp | Describes a turn going up toward the left. e.g. |
BranchDown | Describes a turn going down toward the left. e.g. |
BranchJoin | Describes a T-join of a path going up and down toward the left. e.g. |
BranchContinue | Describes a path going up and down. e.g. |
BranchEmpty | Describes a part that does NOT contain a path piece. e.g. |
Instances
Eq BranchPath Source # | |
Defined in Data.Tree.Render.Text (==) :: BranchPath -> BranchPath -> Bool # (/=) :: BranchPath -> BranchPath -> Bool # | |
Ord BranchPath Source # | |
Defined in Data.Tree.Render.Text compare :: BranchPath -> BranchPath -> Ordering # (<) :: BranchPath -> BranchPath -> Bool # (<=) :: BranchPath -> BranchPath -> Bool # (>) :: BranchPath -> BranchPath -> Bool # (>=) :: BranchPath -> BranchPath -> Bool # max :: BranchPath -> BranchPath -> BranchPath # min :: BranchPath -> BranchPath -> BranchPath # | |
Show BranchPath Source # | |
Defined in Data.Tree.Render.Text showsPrec :: Int -> BranchPath -> ShowS # show :: BranchPath -> String # showList :: [BranchPath] -> ShowS # |
data LocalContext label Source #
Local context about a node.
LocalContext | |
|
data RenderOptionsM m string label Source #
Options used for rendering a Tree
.
RenderOptions | |
|
type RenderOptions = RenderOptionsM (Writer (DList Char)) Source #
An alias of RenderOptionsM
for producing pure String
renders.
renderTree :: RenderOptions String label -> Tree label -> String Source #
renderForest :: RenderOptions String label -> Forest label -> String Source #
renderTreeM :: Monad m => RenderOptionsM m string label -> Tree label -> m () Source #
Renders a pretty printed Tree
within a monadic context.
renderForestM :: Monad m => RenderOptionsM m string label -> Forest label -> m () Source #
Renders a pretty printed Forest
within a monadic context.
:: (label -> String) | Shows a |
-> RenderOptions String label |
A simplified tracedRenderOptionsM
specialized to RenderOptions
.
tracedRenderOptionsAscii Source #
:: (label -> String) | Shows a |
-> RenderOptions String label |
A simplified tracedRenderOptionsAsciiM
specialized to RenderOptions
.
middleCutRenderOptions Source #
:: (label -> String) | Shows a |
-> RenderOptions String label |
A simplified middleCutRenderOptionsM
specialized to RenderOptions
.
:: (label -> String) | Shows a |
-> RenderOptions String label |
A simplified zigZagRenderOptionsM
specialized to RenderOptions
.
:: String | The string used for a tab. |
-> (label -> String) | Shows a |
-> RenderOptions String label |
A simplified tabbedRenderOptionsM
specialized to RenderOptions
.
:: Monad m | |
=> (String -> string) | Promotes a |
-> (string -> m ()) | Writes a |
-> (label -> m string) | Shows a |
-> RenderOptionsM m string label |
Options for rendering a line-traced tree using unicode drawing characters.
This uses:
BranchUp -> "╭─" BranchDown -> "╰─" BranchJoin -> "├─" BranchContinue -> "│ " BranchEmpty -> " "
oNodeMarker = \case Just {} -> "● " Nothing -> "●"
tracedRenderOptionsAsciiM Source #
:: Monad m | |
=> (String -> string) | Promotes a |
-> (string -> m ()) | Writes a |
-> (label -> m string) | Shows a |
-> RenderOptionsM m string label |
Options for rendering a line-traced tree using ASCII characters.
This uses:
BranchUp -> ",-" BranchDown -> "`-" BranchJoin -> "|-" BranchContinue -> "| " BranchEmpty -> " "
oNodeMarker = \case Just {} -> "o " Nothing -> "o"
middleCutRenderOptionsM Source #
:: Monad m | |
=> (String -> string) | Promotes a |
-> (string -> m ()) | Writes a |
-> (label -> m string) | Shows a |
-> RenderOptionsM m string label |
A variety on tracedRenderOptionsM
where the path tracing is
performed in a zig-zag-like fashion such that there is a cut down
the middle of a node's children.
:: Monad m | |
=> (String -> string) | Promotes a |
-> (string -> m ()) | Writes a |
-> (label -> m string) | Shows a |
-> RenderOptionsM m string label |
A variety on tracedRenderOptionsM
where the path tracing is
performed in a zig-zag fashion.