Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Configurable text rendering of trees.
Synopsis
- data ParentLocation
- data ChildOrder
- data BranchPath
- renderTreeM :: Monad m => RenderOptionsM m string label -> Tree label -> m ()
- data RenderOptionsM m string label = RenderOptions {
- oParentLocation :: ParentLocation
- oChildOrder :: ChildOrder
- oVerticalPad :: Int
- oPrependNewLine :: Bool
- oFromString :: String -> string
- oWrite :: string -> m ()
- oShowNodeLabel :: label -> string
- oGetNodeMarker :: label -> string
- oShowBranchPath :: BranchPath -> string
- tracedRenderOptionsM :: (String -> string) -> (string -> m ()) -> (label -> string) -> RenderOptionsM m string label
- tracedRenderOptionsAsciiM :: (String -> string) -> (string -> m ()) -> (label -> string) -> RenderOptionsM m string label
- renderTree :: RenderOptions String label -> Tree label -> String
- type RenderOptions = RenderOptionsM (Writer (DList Char))
- tracedRenderOptions :: (label -> String) -> RenderOptions String label
- tracedRenderOptionsAscii :: (label -> String) -> RenderOptions String label
Documentation
data ParentLocation Source #
Describes where a parent node is rendered, relative to its children.
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 # |
renderTreeM :: Monad m => RenderOptionsM m string label -> Tree label -> m () Source #
Renders a pretty printed tree within a monadic context.
data RenderOptionsM m string label Source #
Options used for rendering a 'Tree label'.
RenderOptions | |
|
:: (String -> string) | Promotes a |
-> (string -> m ()) | Writes a |
-> (label -> string) | Shows a |
-> RenderOptionsM m string label |
Options for producing a line-traced tree using unicode drawing characters.
This uses: BranchUp -> "╭─" BranchDown -> "╰─" BranchJoin -> "├─" BranchContinue -> "│ " BranchEmpty -> " "
tracedRenderOptionsAsciiM Source #
:: (String -> string) | Promotes a |
-> (string -> m ()) | Writes a |
-> (label -> string) | Shows a |
-> RenderOptionsM m string label |
Options for producing a line-traced tree using ASCII characters.
This uses: BranchUp -> ",-" BranchDown -> "`-" BranchJoin -> "|-" BranchContinue -> "| " BranchEmpty -> " "
renderTree :: RenderOptions String label -> Tree label -> String Source #
type RenderOptions = RenderOptionsM (Writer (DList Char)) Source #
An alias of RenderOptionsM
for producing pure String
renders.
:: (label -> String) | Shows a |
-> RenderOptions String label |
Simplified tracedRenderOptionsM
when using RenderOptionsM
.
tracedRenderOptionsAscii Source #
:: (label -> String) | Shows a |
-> RenderOptions String label |
Simplified tracedRenderOptionsAsciiM
when using RenderOptionsM
.