tree-render-text-0.2.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

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 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 RenderOptionsM m string label Source #

Options used for rendering a 'Tree label'.

Constructors

RenderOptions 

Fields

  • oParentLocation :: ParentLocation

    Controls where parent nodes are rendered.

  • oChildOrder :: ChildOrder

    Controls the order a node's children are rendered.

  • oVerticalPad :: Int

    The amount of vertical spacing between nodes.

  • oPrependNewline :: Bool

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

  • oFromString :: String -> string

    Promotes a String to a string.

  • oWrite :: string -> m ()

    Writes a string.

  • oShowNodeLabel :: label -> string

    Shows a rootLabel.

  • oGetNodeMarker :: label -> string

    Get the marker for a node. Although this takes as input a node's label, this should not render the label itself. The returned value should contain no newlines.

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

    Simple use cases would use a constant function ignoring the label value.

  • oForestRootMarker :: string

    The marker used for rendering an artificial root when rendering Forests. The returned value should contain no newlines.

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

tracedRenderOptions Source #

Arguments

:: (label -> String)

Shows a rootLabel.

-> RenderOptions String label 

Simplified tracedRenderOptionsM when using RenderOptionsM.

tracedRenderOptionsAscii Source #

Arguments

:: (label -> String)

Shows a rootLabel.

-> RenderOptions String label 

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

Renders a Tree a pretty printed tree as a String.

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

Renders a Forest a pretty printed tree as a String.

tracedRenderOptionsM Source #

Arguments

:: (String -> string)

Promotes a String to a string.

-> (string -> m ())

Writes a string.

-> (label -> string)

Shows a rootLabel.

-> RenderOptionsM m string label 

Options for producing a line-traced tree using unicode drawing characters.

This uses:

BranchUp       -> "╭─"
BranchDown     -> "╰─"
BranchJoin     -> "├─"
BranchContinue -> "│ "
BranchEmpty    -> "  "

tracedRenderOptionsAsciiM Source #

Arguments

:: (String -> string)

Promotes a String to a string.

-> (string -> m ())

Writes a string.

-> (label -> string)

Shows a rootLabel.

-> RenderOptionsM m string label 

Options for producing a line-traced tree using ASCII characters.

This uses:

BranchUp       -> ",-"
BranchDown     -> "`-"
BranchJoin     -> "|-"
BranchContinue -> "| "
BranchEmpty    -> "  "

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.