{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE Safe #-}
module Data.Tree.Render.Text (
ParentLocation(..),
ChildOrder(..),
BranchPath(..),
LocalContext(..),
RenderOptionsM(..),
RenderOptions,
renderTree,
renderForest,
renderTreeM,
renderForestM,
tracedRenderOptions,
tracedRenderOptionsAscii,
middleCutRenderOptions,
zigZagRenderOptions,
tabbedRenderOptions,
tracedRenderOptionsM,
tracedRenderOptionsAsciiM,
middleCutRenderOptionsM,
zigZagRenderOptionsM,
tabbedRenderOptionsM,
) where
import qualified Control.Monad.State.Strict as M
import qualified Control.Monad.Writer as M
import qualified Data.List as List
import qualified Data.Maybe as Maybe
import Data.Monoid ( Endo(Endo, appEndo) )
import qualified Data.Tree as Tree
import Data.Tree ( Tree, Forest )
type DList a = Endo [a]
runDListWriter :: M.Writer (DList a) () -> [a]
runDListWriter = ($ []) . appEndo . M.execWriter
tellDList :: [a] -> M.Writer (DList a) ()
tellDList s = M.tell $ Endo (s <>)
data ParentLocation
= ParentBeforeChildren
| ParentAfterChildren
| ParentBetweenChildren
| ParentAtChildIndex Int
deriving (Show, Eq, Ord)
data ChildOrder
= FirstToLast
| LastToFirst
deriving (Show, Eq, Ord)
data BranchPath
= BranchUp
| BranchDown
| BranchJoin
| BranchContinue
| BranchEmpty
deriving (Show, Eq, Ord)
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
}
mkStringRenderOptionsM
:: Monad m
=> (Bool -> String)
-> (BranchPath -> String)
-> (String -> string)
-> (string -> m ())
-> (label -> m string)
-> RenderOptionsM m string label
mkStringRenderOptionsM showMarker showPath fromStr write showLabel
= RenderOptions
{ oParentLocation = const loc
, oChildOrder = const ord
, oVerticalPad = 0
, oPrependNewline = False
, oWriteNewline = write newline
, oWrite = write
, oShowNodeLabel = maybe nil showLabel
, oNodeMarker = \case
Just {} -> node
Nothing -> root
, oShowBranchPath = \case
BranchUp -> up
BranchDown -> down
BranchJoin -> join
BranchContinue -> continue
BranchEmpty -> empty
}
where
loc = pure ParentBeforeChildren
ord = pure FirstToLast
nil = pure $ fromStr ""
node = pure $ fromStr $ showMarker True
root = pure $ fromStr $ showMarker False
up = fromStr $ showPath BranchUp
down = fromStr $ showPath BranchDown
join = fromStr $ showPath BranchJoin
continue = fromStr $ showPath BranchContinue
empty = fromStr $ showPath BranchEmpty
newline = fromStr "\n"
unicodeMarker :: Bool -> String
unicodeMarker = \case
True -> "● "
False -> "●"
unicodePath :: BranchPath -> String
unicodePath = \case
BranchUp -> "╭─"
BranchDown -> "╰─"
BranchJoin -> "├─"
BranchContinue -> "│ "
BranchEmpty -> " "
tracedRenderOptionsM
:: Monad m
=> (String -> string)
-> (string -> m ())
-> (label -> m string)
-> RenderOptionsM m string label
tracedRenderOptionsM = mkStringRenderOptionsM unicodeMarker unicodePath
tracedRenderOptionsAsciiM
:: Monad m
=> (String -> string)
-> (string -> m ())
-> (label -> m string)
-> RenderOptionsM m string label
tracedRenderOptionsAsciiM = mkStringRenderOptionsM marker path
where
marker = \case
True -> "o "
False -> "o"
path = \case
BranchUp -> ",-"
BranchDown -> "`-"
BranchJoin -> "|-"
BranchContinue -> "| "
BranchEmpty -> " "
middleCutRenderOptionsM
:: Monad m
=> (String -> string)
-> (string -> m ())
-> (label -> m string)
-> RenderOptionsM m string label
middleCutRenderOptionsM fromStr write showLabel = options
{ oParentLocation = pure . \case
Nothing -> ParentBeforeChildren
Just LocalContext
{ lcLitterIndex = index
, lcLitterSize = size
} -> case index < (size `div` 2) of
True -> ParentBeforeChildren
False -> ParentAfterChildren
}
where
options = tracedRenderOptionsM fromStr write showLabel
zigZagRenderOptionsM
:: Monad m
=> (String -> string)
-> (string -> m ())
-> (label -> m string)
-> RenderOptionsM m string label
zigZagRenderOptionsM fromStr write showLabel = options
{ oParentLocation = pure . \case
Nothing -> ParentBeforeChildren
Just LocalContext
{ lcCurrentDepth = depth
} -> case depth `mod` 2 of
0 -> ParentBeforeChildren
_ -> ParentAfterChildren
}
where
options = tracedRenderOptionsM fromStr write showLabel
tabbedRenderOptionsM
:: Monad m
=> String
-> (String -> string)
-> (string -> m ())
-> (label -> m string)
-> RenderOptionsM m string label
tabbedRenderOptionsM tab = mkStringRenderOptionsM marker path
where
marker = const ""
path = const tab
type RenderOptions = RenderOptionsM (M.Writer (DList Char))
tracedRenderOptions
:: (label -> String)
-> RenderOptions String label
tracedRenderOptions = tracedRenderOptionsM id tellDList . fmap pure
tabbedRenderOptions
:: String
-> (label -> String)
-> RenderOptions String label
tabbedRenderOptions tab = tabbedRenderOptionsM tab id tellDList . fmap pure
middleCutRenderOptions
:: (label -> String)
-> RenderOptions String label
middleCutRenderOptions = middleCutRenderOptionsM id tellDList . fmap pure
zigZagRenderOptions
:: (label -> String)
-> RenderOptions String label
zigZagRenderOptions = zigZagRenderOptionsM id tellDList . fmap pure
tracedRenderOptionsAscii
:: (label -> String)
-> RenderOptions String label
tracedRenderOptionsAscii = tracedRenderOptionsAsciiM id tellDList . fmap pure
renderTree :: RenderOptions String label -> Tree label -> String
renderTree options = runDListWriter . renderTreeM options
renderForest :: RenderOptions String label -> Forest label -> String
renderForest options = runDListWriter . renderForestM options
renderTreeM :: Monad m => RenderOptionsM m string label -> Tree label -> m ()
renderTreeM options tree = M.evalStateT action options
where
action = render lc []
lc = LocalContext
{ lcCurrentNode = tree
, lcCurrentDepth = 0
, lcLitterIndex = 0
, lcLitterSize = 1
}
catMaybes :: Tree (Maybe label) -> Maybe (Tree label)
catMaybes = \case
Tree.Node
{ Tree.rootLabel = mLabel
, Tree.subForest = kids
} -> case mLabel of
Nothing -> Nothing
Just label -> Just Tree.Node
{ Tree.rootLabel = label
, Tree.subForest = Maybe.mapMaybe catMaybes kids
}
renderForestM :: Monad m => RenderOptionsM m string label -> Forest label -> m ()
renderForestM options trees = do
let forestTree = Tree.Node Nothing $ map (fmap Just) trees
let flattenLc = \case
Nothing -> Nothing
Just lc ->
let node = lcCurrentNode lc
in case catMaybes node of
Nothing -> Nothing
Just node' -> Just lc { lcCurrentNode = node' }
let options' = options
{ oShowNodeLabel = oShowNodeLabel options . maybe Nothing id
, oParentLocation = oParentLocation options . flattenLc
, oChildOrder = oChildOrder options . flattenLc
, oNodeMarker = oNodeMarker options . flattenLc
}
renderTreeM options' forestTree
type Render string label m = M.StateT (RenderOptionsM m string label) m
renderString :: Monad m => string -> Render string label m ()
renderString s = do
w <- M.gets oWrite
M.lift $ w s
writeNewline :: Monad m => Render string label m ()
writeNewline = M.gets oWriteNewline >>= M.lift
render :: Monad m => LocalContext label -> [BranchPath] -> Render string label m ()
render lc trail = case lcCurrentNode lc of
Tree.Node
{ Tree.rootLabel = label
, Tree.subForest = kids'
} -> do
parentLoc <- M.gets (flip oParentLocation $ Just lc) >>= M.lift
childOrder <- M.gets (flip oChildOrder $ Just lc) >>= M.lift
let renderCurr = do
M.gets oPrependNewline >>= \case
True -> writeNewline
False -> M.modify' $ \st -> st
{ oPrependNewline = True
}
renderTrail trail
marker <- M.gets (flip oNodeMarker $ Just lc) >>= M.lift
renderString marker
shownLabel <- M.gets (flip oShowNodeLabel $ Just label) >>= M.lift
renderString shownLabel
let kidCount = length kids'
let kids =
let f = case childOrder of
FirstToLast -> id
LastToFirst -> reverse
in flip map (f $ zip kids' [0..]) $ \(kid, idx) -> LocalContext
{ lcCurrentNode = kid
, lcCurrentDepth = lcCurrentDepth lc + 1
, lcLitterIndex = idx
, lcLitterSize = kidCount
}
let trailL = case trail of
BranchDown : rest -> BranchContinue : rest
_ -> trail
trailR = case trail of
BranchUp : rest -> BranchContinue : rest
_ -> trail
renderNextL path lc' = render lc' (path : trailL)
renderNextR path lc' = render lc' (path : trailR)
let index = case parentLoc of
ParentBeforeChildren -> 0
ParentAfterChildren -> kidCount
ParentBetweenChildren -> case childOrder of
FirstToLast -> kidCount `div` 2
LastToFirst -> case kidCount `divMod` 2 of
(d, 0) -> d
(d, _) -> d + 1
ParentAtChildIndex i -> max 0 $ min kidCount i
case (index == 0, index == kidCount) of
(True, _ ) -> do
case initLast kids of
Nothing -> do
renderCurr
Just (ks, k) -> do
renderCurr
M.forM_ ks $ \k' -> do
renderVerticalSpace trailR
renderNextR BranchJoin k'
renderVerticalSpace trailR
renderNextR BranchDown k
( _, True) -> do
case kids of
[] -> do
renderCurr
k : ks -> do
renderNextL BranchUp k
M.forM_ ks $ \k' -> do
renderVerticalSpace trailL
renderNextL BranchJoin k'
renderVerticalSpace trailL
renderCurr
( _ , _ ) -> do
case headMiddleLast kids of
Nothing -> undefined
Just (_, Nothing) -> undefined
Just (k0, Just (ks, kn)) -> do
let (ksL, ksR) = List.splitAt (index - 1) 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
renderVerticalSpace :: Monad m => [BranchPath] -> Render string label m ()
renderVerticalSpace trail = do
n <- M.gets oVerticalPad
M.replicateM_ n $ do
writeNewline
renderTrail $ BranchContinue : trail
renderTrail :: Monad m => [BranchPath] -> Render string label m ()
renderTrail trail = do
showPath <- M.gets oShowBranchPath
let renderPath = renderString . showPath
case trail of
[] -> pure ()
p : ps -> do
M.forM_ (reverse ps) $ renderPath . \case
BranchDown -> BranchEmpty
BranchUp -> BranchEmpty
BranchEmpty -> BranchEmpty
_ -> BranchContinue
renderString $ 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))