{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE Safe #-}
module Data.Tree.Render.Text (
ParentLocation(..),
ChildOrder(..),
BranchPath(..),
renderTreeM,
RenderOptionsM(..),
tracedRenderOptionsM,
tracedRenderOptionsAsciiM,
renderTree,
RenderOptions,
tracedRenderOptions,
tracedRenderOptionsAscii,
) where
import qualified Control.Monad.State.Strict as M
import qualified Control.Monad.Writer as M
import qualified Data.List as List
import Data.Monoid ( Endo(Endo, appEndo) )
import qualified Data.Tree as Tree
import Data.Tree ( Tree )
type DList a = Endo [a]
tellDList :: [a] -> M.Writer (DList a) ()
tellDList s = M.tell $ Endo (s <>)
data ParentLocation
= ParentBeforeChildren
| ParentAfterChildren
| ParentBetweenChildren
deriving (Show, Eq, Ord)
data ChildOrder
= FirstToLast
| LastToFirst
deriving (Show, Eq, Ord)
data BranchPath
= BranchUp
| BranchDown
| BranchJoin
| BranchContinue
| BranchEmpty
deriving (Show, Eq, Ord)
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
}
type RenderOptions = RenderOptionsM (M.Writer (DList Char))
tracedRenderOptionsM
:: (String -> string)
-> (string -> m ())
-> (label -> string)
-> RenderOptionsM m string label
tracedRenderOptionsM fromString' write' show' = RenderOptions
{ oParentLocation = ParentBeforeChildren
, oChildOrder = FirstToLast
, oVerticalPad = 0
, oPrependNewLine = False
, oFromString = fromString'
, oWrite = write'
, oShowNodeLabel = show'
, oGetNodeMarker = const $ fromString' "● "
, oShowBranchPath = fromString' . \case
BranchUp -> "╭─"
BranchDown -> "╰─"
BranchJoin -> "├─"
BranchContinue -> "│ "
BranchEmpty -> " "
}
tracedRenderOptionsAsciiM
:: (String -> string)
-> (string -> m ())
-> (label -> string)
-> RenderOptionsM m string label
tracedRenderOptionsAsciiM fromString' write' show' =
(tracedRenderOptionsM fromString' write' show')
{ oGetNodeMarker = const $ fromString' "o "
, oShowBranchPath = fromString' . \case
BranchUp -> ",-"
BranchDown -> "`-"
BranchJoin -> "|-"
BranchContinue -> "| "
BranchEmpty -> " "
}
tracedRenderOptions
:: (label -> String)
-> RenderOptions String label
tracedRenderOptions = tracedRenderOptionsM id tellDList
tracedRenderOptionsAscii
:: (label -> String)
-> RenderOptions String label
tracedRenderOptionsAscii = tracedRenderOptionsAsciiM id tellDList
renderTree :: RenderOptions String label -> Tree label -> String
renderTree options = run . renderTreeM options
where
run = ($ "") . appEndo . M.execWriter
renderTreeM :: Monad m => RenderOptionsM m string label -> Tree label -> m ()
renderTreeM options tree = M.evalStateT action options
where
action = render [] tree
type Render string label m = M.StateT (RenderOptionsM m string label) m
write :: Monad m => string -> Render string label m ()
write s = do
w <- M.gets oWrite
M.lift $ w s
render :: Monad m => [BranchPath] -> Tree label -> Render string label m ()
render trail = \case
Tree.Node
{ Tree.rootLabel = label
, Tree.subForest = kids'
} -> do
let renderCurr = do
getMarker <- M.gets oGetNodeMarker
showLabel <- M.gets oShowNodeLabel
M.gets oPrependNewLine >>= \case
True -> renderNewLine
False -> M.modify' $ \st -> st
{ oPrependNewLine = True
}
renderTrail trail
write $ getMarker label
write $ showLabel label
childOrder <- M.gets oChildOrder
let kids = case childOrder of
FirstToLast -> kids'
LastToFirst -> reverse kids'
M.gets oParentLocation >>= \case
ParentBeforeChildren -> do
let renderNext path = render $ path : trail
case initLast kids of
Nothing -> do
renderCurr
Just (ks, k) -> do
renderCurr
M.forM_ ks $ \k' -> do
renderVerticalSpace trail
renderNext BranchJoin k'
renderVerticalSpace trail
renderNext BranchDown k
ParentAfterChildren -> do
let renderNext path = render $ path : trail
case kids of
[] -> do
renderCurr
k : ks -> do
renderNext BranchUp k
M.forM_ ks $ \k' -> do
renderVerticalSpace trail
renderNext BranchJoin k'
renderVerticalSpace trail
renderCurr
ParentBetweenChildren -> do
let trailL = case trail of
BranchDown : rest -> BranchContinue : rest
_ -> trail
trailR = case trail of
BranchUp : rest -> BranchContinue : rest
_ -> trail
renderNextL path = render $ path : trailL
renderNextR path = render $ path : trailR
case headMiddleLast kids of
Nothing -> do
renderCurr
Just (k, Nothing) -> do
case childOrder of
FirstToLast -> do
renderCurr
renderVerticalSpace trailR
renderNextR BranchDown k
LastToFirst -> do
renderNextL BranchUp k
renderVerticalSpace trailL
renderCurr
Just (k0, Just (ks, kn)) -> do
let index = case childOrder of
FirstToLast -> length ks `div` 2
LastToFirst -> case length ks `divMod` 2 of
(d, 0) -> d
(d, _) -> d + 1
let (ksL, ksR) = List.splitAt index ks
renderNextL BranchUp k0
M.forM_ ksL $ \k -> do
renderVerticalSpace trailL
renderNextL BranchJoin k
renderVerticalSpace trailL
renderCurr
M.forM_ ksR $ \k -> do
renderVerticalSpace trailR
renderNextR BranchJoin k
renderVerticalSpace trailR
renderNextR BranchDown kn
renderNewLine :: Monad m => Render string label m ()
renderNewLine = do
from <- M.gets oFromString
write $ from "\n"
renderVerticalSpace :: Monad m => [BranchPath] -> Render string label m ()
renderVerticalSpace trail = do
n <- M.gets oVerticalPad
M.replicateM_ n $ do
renderNewLine
renderTrail $ BranchContinue : trail
renderTrail :: Monad m => [BranchPath] -> Render string label m ()
renderTrail trail = do
showPath <- M.gets oShowBranchPath
let renderPath = write . showPath
case trail of
[] -> pure ()
p : ps -> do
M.forM_ (reverse ps) $ renderPath . \case
BranchDown -> BranchEmpty
BranchUp -> BranchEmpty
BranchEmpty -> BranchEmpty
_ -> BranchContinue
write $ showPath p
initLast :: [a] -> Maybe ([a], a)
initLast = \case
[] -> Nothing
xs -> Just (init xs, last xs)
headMiddleLast :: [a] -> Maybe (a, Maybe ([a], a))
headMiddleLast = \case
[] -> Nothing
x : xs -> case xs of
[] -> Just (x, Nothing)
_ -> Just (x, Just (init xs, last xs))