tree-render-text-0.4.0.0: Configurable text rendering of trees.

Safe HaskellSafe
LanguageHaskell2010

Data.Tree.Render.Text

Description

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

Documentation

data ParentLocation Source #

Describes where a parent node is rendered, relative to its children.

Constructors

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 FirstToLast and rounded up when using LastToFirst.

ParentAtChildIndex Int

This is a value from [0, 1, ..., length children] inclusive. (Values outside this range are clamped to the closest valid value.)

A value of 0 makes the parent rendered before any of its children A value of length children makes the parent rendered after all of its children. Other values place the parent in the corresponding spot between its children.

data ChildOrder Source #

Describes the render order of a node's children.

Constructors

FirstToLast 
LastToFirst 

data BranchPath Source #

A part of a path along a rendered tree.

Constructors

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. " "

data LocalContext label Source #

Local context about a node.

Constructors

LocalContext 

Fields

data RenderOptionsM m string label Source #

Options used for rendering a Tree.

Constructors

RenderOptions 

Fields

  • oParentLocation :: Maybe (LocalContext label) -> m ParentLocation

    Controls where parent nodes are rendered.

    A value of Nothing is passed when rending the artificial root of a Forest.

    Simple use cases would use a constant function ignoring the local context.

  • oChildOrder :: Maybe (LocalContext label) -> m ChildOrder

    Controls the order a node's children are rendered.

    A value of Nothing is passed when rending the artificial root of a Forest.

    Simple use cases would use a constant function ignoring the local context.

  • oVerticalPad :: Int

    The amount of vertical spacing between nodes.

  • oPrependNewline :: Bool

    If True, a newline is prepended to the rendered output.

  • oWriteNewline :: m ()

    Writes a newline.

  • oWrite :: string -> m ()

    Writes a string.

  • oShowNodeLabel :: Maybe label -> m string

    Shows a rootLabel. The returned value should contain no newlines.

  • oNodeMarker :: Maybe (LocalContext label) -> m string

    Get the marker for a node (without rendering its label). The returned value should contain no newlines.

    LocalContext is passed as an argument to allow things such as:

    • Rendering a node marker differently for labels that fail to pass a test.
    • Highlighting a node currently being visited.
    • Numbered bullets.

    A value of Nothing is passed when rending the artificial root of a Forest.

    Simple use cases would typically ignore the local context.

  • oShowBranchPath :: BranchPath -> string

    Shows a BranchPath. The returned value should contain no newlines and should all be of the same printed width when rendered as text.

type RenderOptions = RenderOptionsM (Writer (DList Char)) Source #

An alias of RenderOptionsM for producing pure String renders.

renderTree :: RenderOptions String label -> Tree label -> String Source #

Renders a Tree to a String.

renderForest :: RenderOptions String label -> Forest label -> String Source #

Renders a Forest to a String.

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.

tracedRenderOptions Source #

Arguments

:: (label -> String)

Shows a rootLabel.

-> RenderOptions String label 

A simplified tracedRenderOptionsM specialized to RenderOptions.

tracedRenderOptionsAscii Source #

Arguments

:: (label -> String)

Shows a rootLabel.

-> RenderOptions String label 

A simplified tracedRenderOptionsAsciiM specialized to RenderOptions.

middleCutRenderOptions Source #

Arguments

:: (label -> String)

Shows a rootLabel.

-> RenderOptions String label 

A simplified middleCutRenderOptionsM specialized to RenderOptions.

zigZagRenderOptions Source #

Arguments

:: (label -> String)

Shows a rootLabel.

-> RenderOptions String label 

A simplified zigZagRenderOptionsM specialized to RenderOptions.

tabbedRenderOptions Source #

Arguments

:: String

The string used for a tab.

-> (label -> String)

Shows a rootLabel.

-> RenderOptions String label 

A simplified tabbedRenderOptionsM specialized to RenderOptions.

tracedRenderOptionsM Source #

Arguments

:: Monad m 
=> (String -> string)

Promotes a String to a string.

-> (string -> m ())

Writes a string.

-> (label -> m string)

Shows a rootLabel.

-> 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 #

Arguments

:: Monad m 
=> (String -> string)

Promotes a String to a string.

-> (string -> m ())

Writes a string.

-> (label -> m string)

Shows a rootLabel.

-> 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 #

Arguments

:: Monad m 
=> (String -> string)

Promotes a String to a string.

-> (string -> m ())

Writes a string.

-> (label -> m string)

Shows a rootLabel.

-> 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.

zigZagRenderOptionsM Source #

Arguments

:: Monad m 
=> (String -> string)

Promotes a String to a string.

-> (string -> m ())

Writes a string.

-> (label -> m string)

Shows a rootLabel.

-> RenderOptionsM m string label 

A variety on tracedRenderOptionsM where the path tracing is performed in a zig-zag fashion.

tabbedRenderOptionsM Source #

Arguments

:: Monad m 
=> String

The string used for a tab.

-> (String -> string)

Promotes a String to a string.

-> (string -> m ())

Writes a string.

-> (label -> m string)

Shows a rootLabel.

-> RenderOptionsM m string label 

Options for rendering a tree in rows indented only by tabs.