Tree datastructures: Difference between revisions

New post.
m (→‎{{header|Python}}: added zkl header)
(New post.)
(36 intermediate revisions by 13 users not shown)
Line 1:
{{draft task}}
The following shows a tree of data with nesting denoted by visual levels of indentation:
<pre>RosettaCode
Line 35:
* It's all about showing aspects of the contrasting datastructures as they hold the tree.
* Comparing nested datastructures is secondary - saving formatted output as a string then a string compare would suffice for this task, if its easier.
* The word "trolling" is substituted for the original, less appropriate, "golfing" in the tree above as golfing can be friendly fun! (just not for RC examples). '''Please update language examples appropriately'''.
<br>
 
Show all output on this page.
 
=={{header|11l}}==
{{trans|Nim}}
 
<syntaxhighlight lang="11l">T NNode
String value
[NNode] children
 
F (value)
.value = value
 
F add(node)
.children.append(node)
 
F.const to_str(depth) -> String
V result = (‘ ’ * depth)‘’(.value)"\n"
L(child) .children
result ‘’= child.to_str(depth + 1)
R result
 
F String()
R .to_str(0)
 
T INode
String value
Int level
F (value, level)
.value = value
.level = level
 
F to_indented(node)
[INode] result
F add_node(NNode node, Int level) -> N
@result.append(INode(node.value, level))
L(child) node.children
@add_node(child, level + 1)
add_node(node, 0)
R result
 
F to_nested(tree)
[NNode] stack
V nnode = NNode(tree[0].value)
L(i) 1 .< tree.len
V inode = tree[i]
I inode.level > stack.len
stack.append(nnode)
E I inode.level == stack.len
stack.last.children.append(nnode)
E
L inode.level < stack.len
stack.last.children.append(nnode)
nnode = stack.pop()
stack.last.children.append(nnode)
nnode = NNode(inode.value)
 
L stack.len > 0
stack.last.children.append(nnode)
nnode = stack.pop()
 
R nnode
 
print(‘Displaying tree built using nested structure:’)
V nestedTree = NNode(‘RosettaCode’)
V rocks = NNode(‘rocks’)
rocks.add(NNode(‘code’))
rocks.add(NNode(‘comparison’))
rocks.add(NNode(‘wiki’))
V mocks = NNode(‘mocks’)
mocks.add(NNode(‘trolling’))
nestedTree.add(rocks)
nestedTree.add(mocks)
print(nestedTree)
 
print(‘Displaying tree converted to indented structure:’)
V indentedTree = to_indented(nestedTree)
L(node) indentedTree
print((node.level)‘ ’(node.value))
print()
 
print(‘Displaying tree converted back to nested structure:’)
print(to_nested(indentedTree))
 
print(‘Are they equal? ’(I String(nestedTree) == String(to_nested(indentedTree)) {‘yes’} E ‘no’))</syntaxhighlight>
 
{{out}}
<pre>
Displaying tree built using nested structure:
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
 
Displaying tree converted to indented structure:
0 RosettaCode
1 rocks
2 code
2 comparison
2 wiki
1 mocks
2 trolling
 
Displaying tree converted back to nested structure:
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
 
Are they equal? yes
</pre>
 
=={{header|C++}}==
<syntaxhighlight lang="cpp">#include <iomanip>
#include <iostream>
#include <list>
#include <string>
#include <vector>
#include <utility>
#include <vector>
 
class nest_tree;
 
bool operator==(const nest_tree&, const nest_tree&);
 
class nest_tree {
public:
explicit nest_tree(const std::string& name) : name_(name) {}
nest_tree& add_child(const std::string& name) {
children_.emplace_back(name);
return children_.back();
}
void print(std::ostream& out) const {
print(out, 0);
}
const std::string& name() const {
return name_;
}
const std::list<nest_tree>& children() const {
return children_;
}
bool equals(const nest_tree& n) const {
return name_ == n.name_ && children_ == n.children_;
}
private:
void print(std::ostream& out, int level) const {
std::string indent(level * 4, ' ');
out << indent << name_ << '\n';
for (const nest_tree& child : children_)
child.print(out, level + 1);
}
std::string name_;
std::list<nest_tree> children_;
};
 
bool operator==(const nest_tree& a, const nest_tree& b) {
return a.equals(b);
}
 
class indent_tree {
public:
explicit indent_tree(const nest_tree& n) {
items_.emplace_back(0, n.name());
from_nest(n, 0);
}
void print(std::ostream& out) const {
for (const auto& item : items_)
std::cout << item.first << ' ' << item.second << '\n';
}
nest_tree to_nest() const {
nest_tree n(items_[0].second);
to_nest_(n, 1, 0);
return n;
}
private:
void from_nest(const nest_tree& n, int level) {
for (const nest_tree& child : n.children()) {
items_.emplace_back(level + 1, child.name());
from_nest(child, level + 1);
}
}
size_t to_nest_(nest_tree& n, size_t pos, int level) const {
while (pos < items_.size() && items_[pos].first == level + 1) {
nest_tree& child = n.add_child(items_[pos].second);
pos = to_nest_(child, pos + 1, level + 1);
}
return pos;
}
std::vector<std::pair<int, std::string>> items_;
};
 
int main() {
nest_tree n("RosettaCode");
auto& child1 = n.add_child("rocks");
auto& child2 = n.add_child("mocks");
child1.add_child("code");
child1.add_child("comparison");
child1.add_child("wiki");
child2.add_child("trolling");
std::cout << "Initial nest format:\n";
n.print(std::cout);
indent_tree i(n);
std::cout << "\nIndent format:\n";
i.print(std::cout);
nest_tree n2(i.to_nest());
std::cout << "\nFinal nest format:\n";
n2.print(std::cout);
 
std::cout << "\nAre initial and final nest formats equal? "
<< std::boolalpha << n.equals(n2) << '\n';
return 0;
}</syntaxhighlight>
 
{{out}}
<pre>
Initial nest format:
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
 
Indent format:
0 RosettaCode
1 rocks
2 code
2 comparison
2 wiki
1 mocks
2 trolling
 
Final nest format:
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
 
Are initial and final nest formats equal? true
</pre>
 
=={{header|Go}}==
<langsyntaxhighlight lang="go">package main
 
import (
Line 123 ⟶ 374:
 
fmt.Println("\nRound trip test satisfied? ", s1 == s2)
}</langsyntaxhighlight>
 
{{out}}
Line 159 ⟶ 410:
Round trip test satisfied? true
</pre>
 
=={{header|Haskell}}==
The task is all about the isomorphism between different representations of a nested list structure. Therefore the solution is given in terms of the isomorphisms.
 
<syntaxhighlight lang="haskell">{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableSuperClasses #-}
{-# LANGUAGE TypeApplications #-}
 
import Data.List (span)
 
-- A nested tree structure.
-- Using `Maybe` allows encoding several zero-level items
-- or irregular lists (see test example)
data Nest a = Nest (Maybe a) [Nest a]
deriving Eq
 
instance Show a => Show (Nest a) where
show (Nest (Just a) []) = show a
show (Nest (Just a) s) = show a ++ show s
show (Nest Nothing []) = "\"\""
show (Nest Nothing s) = "\"\"" ++ show s
 
-- An indented tree structure.
type Indent a = [(Int, a)]
 
-- class for isomorphic types
class Iso b a => Iso a b where
from :: a -> b
 
-- A bijection from nested form to indent form
instance Iso (Nest a) (Indent a) where
from = go (-1)
where
go n (Nest a t) =
case a of
Just a -> (n, a) : foldMap (go (n + 1)) t
Nothing -> foldMap (go (n + 1)) t
 
-- A bijection from indent form to nested form
instance Iso (Indent a) (Nest a) where
from = revNest . foldl add (Nest Nothing [])
where
add t (d,x) = go 0 t
where
go n (Nest a s) =
case compare n d of
EQ -> Nest a $ Nest (Just x) [] : s
LT -> case s of
h:t -> Nest a $ go (n+1) h : t
[] -> go n $ Nest a [Nest Nothing []]
GT -> go (n-1) $ Nest Nothing [Nest a s]
 
revNest (Nest a s) = Nest a (reverse $ revNest <$> s)
 
-- A bijection from indent form to a string
instance Iso (Indent String) String where
from = unlines . map process
where
process (d, s) = replicate (4*d) ' ' ++ s
 
-- A bijection from a string to indent form
instance Iso String (Indent String) where
from = map process . lines
where
process s = let (i, a) = span (== ' ') s
in (length i `div` 4, a)
 
-- A bijection from nest form to a string via indent form
instance Iso (Nest String) String where
from = from @(Indent String) . from
 
-- A bijection from a string to nest form via indent form
instance Iso String (Nest String) where
from = from @(Indent String) . from</syntaxhighlight>
 
Testing:
<syntaxhighlight lang="haskell">test = unlines
[ "RosettaCode"
, " rocks"
, " code"
, " comparison"
, " wiki"
, " mocks"
, " trolling"
, "Some lists"
, " may"
, " be"
, " irregular" ]
 
itest :: Indent String
itest = from test
 
ttest :: Nest String
ttest = from test</syntaxhighlight>
 
<pre>λ> mapM_ print itest
(0,"RosettaCode")
(1,"rocks")
(2,"code")
(2,"comparison")
(2,"wiki")
(1,"mocks")
(2,"trolling")
(0,"Some lists")
(3,"may")
(2,"be")
(1,"irregular")
 
λ> ttest
""["RosettaCode"["rocks"["code","comparison","wiki"],"mocks"["trolling"]],
"Some lists"[""[""["may"],"be"],"irregular"]]
 
λ> putStr $ from (from test :: Indent String)
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
Some lists
may
be
irregular
 
λ> putStr $ from (from test :: Nest String)
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
Some lists
may
be
irregular
 
λ> test == from (from test :: Nest String)
True
 
λ> test == from (from test :: Indent String)
True
 
λ> itest == from (from itest :: String)
True
 
λ> itest == from (from itest :: Nest String)
True
 
λ> ttest == from (from ttest :: String)
True
 
λ> ttest == from (from ttest :: Indent String)
True</pre>
 
 
And less satisfyingly and instructively – just relying a little passively on the existing Data.Tree,
we might also write something like:
 
<syntaxhighlight lang="haskell">import Data.Bifunctor (bimap, first)
import Data.Char (isSpace)
import Data.List (find)
import Data.Tree (Forest, Tree (..), drawTree)
 
-------- MAPPINGS BETWEEN INDENTED LINES AND TREES -------
 
forestFromNestLevels :: [(Int, String)] -> Forest String
forestFromNestLevels = go
where
go [] = []
go ((n, v) : xs) =
uncurry (:) $
bimap (Node v . go) go (span ((n <) . fst) xs)
 
indentLevelsFromLines :: [String] -> [(Int, String)]
indentLevelsFromLines xs =
let pairs = first length . span isSpace <$> xs
indentUnit = maybe 1 fst (find ((0 <) . fst) pairs)
in first (`div` indentUnit) <$> pairs
 
outlineFromForest ::
(String -> String -> String) ->
String ->
Forest String ->
String
outlineFromForest showRoot tabString forest =
let go indent node =
showRoot indent (rootLabel node) :
(subForest node >>= go ((<>) tabString indent))
in unlines $ forest >>= go ""
 
-------------------------- TESTS -------------------------
main :: IO ()
main = do
putStrLn "Tree representation parsed directly:\n"
putStrLn $ drawTree $ Node "" nativeForest
 
let levelPairs = indentLevelsFromLines test
putStrLn "\n[(Level, Text)] list from lines:\n"
mapM_ print levelPairs
 
putStrLn "\n\nTrees from indented text:\n"
let trees = forestFromNestLevels levelPairs
putStrLn $ drawTree $ Node "" trees
 
putStrLn "Indented text from trees:\n"
putStrLn $ outlineFromForest (<>) " " trees
 
test :: [String]
test =
[ "RosettaCode",
" rocks",
" code",
" comparison",
" wiki",
" mocks",
" trolling",
"Some lists",
" may",
" be",
" irregular"
]
 
nativeForest :: Forest String
nativeForest =
[ Node
"RosettaCode"
[ Node
"rocks"
[ Node "code" [],
Node "comparison" [],
Node "wiki" []
],
Node
"mocks"
[Node "trolling" []]
],
Node
"Some lists"
[ Node "may" [],
Node "be" [],
Node "irregular" []
]
]</syntaxhighlight>
{{Out}}
<pre>Tree representation parsed directly:
 
|
+- RosettaCode
| |
| +- rocks
| | |
| | +- code
| | |
| | +- comparison
| | |
| | `- wiki
| |
| `- mocks
| |
| `- trolling
|
`- Some lists
|
+- may
|
+- be
|
`- irregular
 
 
[(Level, Text)] list from lines:
 
(0,"RosettaCode")
(1,"rocks")
(2,"code")
(2,"comparison")
(2,"wiki")
(1,"mocks")
(2,"trolling")
(0,"Some lists")
(3,"may")
(2,"be")
(1,"irregular")
 
 
Trees from indented text:
 
|
+- RosettaCode
| |
| +- rocks
| | |
| | +- code
| | |
| | +- comparison
| | |
| | `- wiki
| |
| `- mocks
| |
| `- trolling
|
`- Some lists
|
+- may
|
+- be
|
`- irregular
 
Indented text from trees:
 
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
Some lists
may
be
irregular</pre>
 
=={{header|Java}}==
<syntaxhighlight lang="java">
public class TreeDatastructures {
 
public static void main(String[] args) {
String initialNested = """
Rosetta Code
....rocks
........code
........comparison
........wiki
....mocks
........trolling
""";
System.out.println(initialNested);
String indented = nestedToIndented(initialNested);
System.out.println(indented);
String finalNested = indentedToNested(indented);
System.out.println(finalNested);
 
final boolean equal = ( initialNested.compareTo(finalNested) == 0 );
System.out.println("initialNested = finalNested ? " + equal);
}
private static String nestedToIndented(String nested) {
StringBuilder result = new StringBuilder();
for ( String line : nested.split(LINE_END) ) {
int index = 0;
while ( line.charAt(index) == '.' ) {
index += 1;
}
result.append(String.valueOf(index / 4) + " " + line.substring(index) + LINE_END);
}
return result.toString();
}
 
private static String indentedToNested(String indented) {
StringBuilder result = new StringBuilder();
for ( String line : indented.split(LINE_END) ) {
final int index = line.indexOf(' ');
final int level = Integer.valueOf(line.substring(0, index));
for ( int i = 0; i < level; i++ ) {
result.append("....");
}
result.append(line.substring(index + 1) + LINE_END);
}
return result.toString();
}
private static final String LINE_END = "\n";
 
}
</syntaxhighlight>
{{ out }}
<pre>
Rosetta Code
....rocks
........code
........comparison
........wiki
....mocks
........trolling
 
0 Rosetta Code
1 rocks
2 code
2 comparison
2 wiki
1 mocks
2 trolling
 
Rosetta Code
....rocks
........code
........comparison
........wiki
....mocks
........trolling
 
initialNested = finalNested ? true
</pre>
 
=={{header|jq}}==
'''Adapted from [[#Wren|Wren]]'''
{{works with|jq}}
'''Also works with gojq, the Go implementation of jq'''
 
<syntaxhighlight lang="jq">
# node of a nested representation
def NNode($name; $children): {$name, $children};
 
# node of an indented representation:
def INode($level; $name): {$level, $name};
 
# Output: string representation of an NNode structure
def printNest:
. as $nested
# input: string so far
| def printNest($n; $level):
if ($level == 0) then "\n==Nest form==\n\n" else . end
| reduce ($n.children[], null) as $c ( . + "\((" " * $level) // "")\($n.name)\n";
if $c == null then .
else . + (" " * ($level + 1)) | printNest($c; $level + 1)
end );
printNest($nested; 0);
 
# input: an INode structure
# output: the corresponding NNode structure
def toNest:
. as $in
| def toNest($iNodes; start; level):
{ i: (start + 1),
n: (if (level == 0) then .name = $iNodes[0].name else . end)
}
| until ( (.i >= ($iNodes|length)) or .done;
if ($iNodes[.i].level == level + 1)
then .i as $i
| (NNode($iNodes[$i].name; []) | toNest($iNodes; $i; level+1)) as $c
| .n.children += [$c]
else if ($iNodes[.i].level <= level) then .done = true else . end
end
| .i += 1 )
| .n ;
NNode(""; []) | toNest($in; 0; 0);
 
# Output: string representation of an INode structure
def printIndent:
"\n==Indent form==\n\n"
+ reduce .[] as $n ("";
. + "\($n.level) \($n.name)\n") ;
 
# output: representation using INode
def toIndent:
def toIndent($n; level):
. + [INode(level; $n.name)]
+ reduce $n.children[] as $c ([];
toIndent($c; level+1) );
. as $in
| [] | toIndent($in; 0);
 
 
### Example
 
def n: NNode(""; []);
def n1: NNode("RosettaCode"; []);
def n2: NNode("rocks"; [NNode("code"; []), NNode("comparison"; []), NNode("wiki"; [])] );
def n3: NNode("mocks"; [NNode("trolling"; [])]);
 
def n123:
n1
| .children += [n2]
| .children += [n3];
 
### The task
def nested:
n123
| printNest ;
 
def indented:
n123
| toIndent
| printIndent;
 
def roundtrip:
n123
| toIndent
| toNest
| printNest;
 
def task:
nested as $nested
| roundtrip as $roundtrip
| $nested, indented, $roundtrip,
"\nRound trip test satisfied? \($nested == $roundtrip)" ;
 
task
</syntaxhighlight>
{{output}}
As for [[#Wren|Wren]].
 
=={{header|Julia}}==
<syntaxhighlight lang="julia">const nesttext = """
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
"""
 
function nesttoindent(txt)
ret = ""
windent = gcd(length.([x.match for x in eachmatch(r"\s+", txt)]) .- 1)
for lin in split(txt, "\n")
ret *= isempty(lin) ? "\n" : isspace(lin[1]) ?
replace(lin, r"\s+" => (s) -> "$(length(s)÷windent) ") * "\n" :
"0 " * lin * "\n"
end
return ret, " "^windent
end
 
function indenttonest(txt, indenttext)
ret = ""
for lin in filter(x -> length(x) > 1, split(txt, "\n"))
(num, name) = split(lin, r"\s+", limit=2)
indentnum = parse(Int, num)
ret *= indentnum == 0 ? name * "\n" : indenttext^indentnum * name * "\n"
end
return ret
end
 
indenttext, itext = nesttoindent(nesttext)
restorednesttext = indenttonest(indenttext, itext)
 
println("Original:\n", nesttext, "\n")
println("Indent form:\n", indenttext, "\n")
println("Back to nest form:\n", restorednesttext, "\n")
println("original == restored: ", strip(nesttext) == strip(restorednesttext))
</syntaxhighlight>{{out}}
<pre>
Original:
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
 
 
Indent form:
0 RosettaCode
1 rocks
2 code
2 comparison
2 wiki
1 mocks
2 trolling
 
 
 
Back to nest form:
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
 
 
original == restored: true
</pre>
 
=={{header|Nim}}==
 
<syntaxhighlight lang="nim">import strformat, strutils
 
 
####################################################################################################
# Nested representation of trees.
# The tree is simply the first node.
 
type
 
NNode*[T] = ref object
value*: T
children*: seq[NNode[T]]
 
 
proc newNNode*[T](value: T; children: varargs[NNode[T]]): NNode[T] =
## Create a node.
NNode[T](value: value, children: @children)
 
 
proc add*[T](node: NNode[T]; children: varargs[NNode[T]]) =
## Add a list of chlidren to a node.
node.children.add children
 
 
proc `$`*[T](node: NNode[T]; depth = 0): string =
## Return a string representation of a tree/node.
result = repeat(' ', 2 * depth) & $node.value & '\n'
for child in node.children:
result.add `$`(child, depth + 1)
 
 
####################################################################################################
# Indented representation of trees.
# The tree is described as the list of the nodes.
 
type
 
INode*[T] = object
value*: T
level*: Natural
 
ITree*[T] = seq[INode[T]]
 
 
proc initINode*[T](value: T; level: Natural): INode[T] =
## Return a new node.
INode[T](value: value, level: level)
 
 
proc initItree*[T](value: T): ITree[T] =
## Return a new tree initialized with the first node (root node).
result = @[initINode(value, 0)]
 
 
proc add*[T](tree: var ITree[T]; nodes: varargs[INode[T]]) =
## Add a list of nodes to the tree.
for node in nodes:
if node.level - tree[^1].level > 1:
raise newException(ValueError, &"wrong level {node.level} in node {node.value}.")
tree.add node
 
 
proc `$`*[T](tree: ITree[T]): string =
## Return a string representation of a tree.
for node in tree:
result.add $node.level & ' ' & $node.value & '\n'
 
 
####################################################################################################
# Conversion between nested form and indented form.
 
proc toIndented*[T](node: NNode[T]): Itree[T] =
## Convert a tree in nested form to a tree in indented form.
 
proc addNode[T](tree: var Itree[T]; node: NNode[T]; level: Natural) =
## Add a node to the tree at the given level.
tree.add initINode(node.value, level)
for child in node.children:
tree.addNode(child, level + 1)
 
result.addNode(node, 0)
 
 
proc toNested*[T](tree: Itree[T]): NNode[T] =
## Convert a tree in indented form to a tree in nested form.
 
var stack: seq[NNode[T]] # Note that stack.len is equal to the current level.
var nnode = newNNode(tree[0].value) # Root.
for i in 1..tree.high:
let inode = tree[i]
if inode.level > stack.len:
# Child.
stack.add nnode
elif inode.level == stack.len:
# Sibling.
stack[^1].children.add nnode
else:
# Branch terminated.
while inode.level < stack.len:
stack[^1].children.add nnode
nnode = stack.pop()
stack[^1].children.add nnode
 
nnode = newNNode(inode.value)
 
# Empty the stack.
while stack.len > 0:
stack[^1].children.add nnode
nnode = stack.pop()
 
result = nnode
 
 
#———————————————————————————————————————————————————————————————————————————————————————————————————
 
when isMainModule:
 
echo "Displaying tree built using nested structure:"
let nestedTree = newNNode("RosettaCode")
let rocks = newNNode("rocks")
rocks.add newNNode("code"), newNNode("comparison"), newNNode("wiki")
let mocks = newNNode("mocks", newNNode("trolling"))
nestedTree.add rocks, mocks
echo nestedTree
 
echo "Displaying tree converted to indented structure:"
let indentedTree = nestedTree.toIndented
echo indentedTree
 
echo "Displaying tree converted back to nested structure:"
echo indentedTree.toNested
 
echo "Are they equal? ", if $nestedTree == $indentedTree.toNested: "yes" else: "no"</syntaxhighlight>
 
{{out}}
<pre>Displaying tree built using nested structure:
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
 
Displaying tree converted to indented structure:
0 RosettaCode
1 rocks
2 code
2 comparison
2 wiki
1 mocks
2 trolling
 
Displaying tree converted back to nested structure:
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
 
Are they equal? yes</pre>
 
=={{header|Perl}}==
{{trans|Raku}}
<syntaxhighlight lang="perl">use strict;
use warnings;
use feature 'say';
use JSON;
use Data::Printer;
 
my $trees = <<~END;
RosettaCode
encourages
code
diversity
comparison
discourages
golfing
trolling
emphasising execution speed
code-golf.io
encourages
golfing
discourages
comparison
END
 
my $level = ' ';
sub nested_to_indent { shift =~ s#^($level*)# ($1 ? length($1)/length $level : 0) . ' ' #egmr }
sub indent_to_nested { shift =~ s#^(\d+)\s*# $level x $1 #egmr }
 
say my $indent = nested_to_indent $trees;
my $nest = indent_to_nested $indent;
 
use Test::More;
is($trees, $nest, 'Round-trip');
done_testing();
 
# Import outline paragraph into native data structure
sub import {
my($trees) = @_;
my $level = ' ';
my $forest;
my $last = -999;
 
for my $branch (split /\n/, $trees) {
$branch =~ m/(($level*))*/;
my $this = $1 ? length($1)/length($level) : 0;
$forest .= do {
if ($this gt $last) { '[' . trim_and_quote($branch) }
elsif ($this lt $last) { ']'x($last-$this).',' . trim_and_quote($branch) }
else { trim_and_quote($branch) }
};
$last = $this;
}
sub trim_and_quote { shift =~ s/^\s*(.*\S)\s*$/"$1",/r }
 
eval $forest . ']' x (1+$last);
}
 
my $forest = import $trees;
say "Native data structure:\n" . np $forest;
say "\nJSON:\n" . encode_json($forest);</syntaxhighlight>
{{out}}
<pre>RosettaCode
1 encourages
2 code
3 diversity
3 comparison
1 discourages
2 golfing
2 trolling
2 emphasising execution speed
code-golf.io
1 encourages
2 golfing
1 discourages
2 comparison
 
ok 1 - Round-trip
1..1
 
Native data structure:
\ [
[0] "RosettaCode",
[1] [
[0] "encourages",
[1] [
[0] "code",
[1] [
[0] "diversity",
[1] "comparison"
]
],
[2] "discourages",
[3] [
[0] "golfing",
[1] "trolling",
[2] "emphasising execution speed"
]
],
[2] "code-golf.io",
[3] [
[0] "encourages",
[1] [
[0] "golfing"
],
[2] "discourages",
[3] [
[0] "comparison"
]
]
]
 
JSON:
["RosettaCode",["encourages",["code",["diversity","comparison"]],"discourages",["golfing","trolling","emphasising execution speed"]],"code-golf.io",["encourages",["golfing"],"discourages",["comparison"]]]</pre>
 
=={{header|Phix}}==
{{libheader|Phix/basics}}
The standard Phix sequence is perfect for handling all of these kinds of structures.
<!--<syntaxhighlight lang="phix">-->
<span style="color: #008080;">function</span> <span style="color: #000000;">text_to_indent</span><span style="color: #0000FF;">(</span><span style="color: #004080;">string</span> <span style="color: #000000;">plain_text</span><span style="color: #0000FF;">)</span>
<span style="color: #004080;">sequence</span> <span style="color: #000000;">lines</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">split</span><span style="color: #0000FF;">(</span><span style="color: #000000;">plain_text</span><span style="color: #0000FF;">,</span><span style="color: #008000;">"\n"</span><span style="color: #0000FF;">,</span><span style="color: #000000;">no_empty</span><span style="color: #0000FF;">:=</span><span style="color: #004600;">true</span><span style="color: #0000FF;">),</span>
<span style="color: #000000;">parents</span> <span style="color: #0000FF;">=</span> <span style="color: #0000FF;">{}</span>
<span style="color: #008080;">for</span> <span style="color: #000000;">i</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span> <span style="color: #008080;">to</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">lines</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">do</span>
<span style="color: #004080;">string</span> <span style="color: #000000;">line</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">trim_tail</span><span style="color: #0000FF;">(</span><span style="color: #000000;">lines</span><span style="color: #0000FF;">[</span><span style="color: #000000;">i</span><span style="color: #0000FF;">]),</span>
<span style="color: #000000;">text</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">trim_head</span><span style="color: #0000FF;">(</span><span style="color: #000000;">line</span><span style="color: #0000FF;">)</span>
<span style="color: #004080;">integer</span> <span style="color: #000000;">indent</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">line</span><span style="color: #0000FF;">)-</span><span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">text</span><span style="color: #0000FF;">)</span>
<span style="color: #000080;font-style:italic;">-- remove any completed parents</span>
<span style="color: #008080;">while</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">parents</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">and</span> <span style="color: #000000;">indent</span><span style="color: #0000FF;"><=</span><span style="color: #000000;">parents</span><span style="color: #0000FF;">[$]</span> <span style="color: #008080;">do</span>
<span style="color: #000000;">parents</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">parents</span><span style="color: #0000FF;">[</span><span style="color: #000000;">1</span><span style="color: #0000FF;">..$-</span><span style="color: #000000;">1</span><span style="color: #0000FF;">]</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">while</span>
<span style="color: #000080;font-style:italic;">-- append potential new parent</span>
<span style="color: #000000;">parents</span> <span style="color: #0000FF;">&=</span> <span style="color: #000000;">indent</span>
<span style="color: #004080;">integer</span> <span style="color: #000000;">depth</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">parents</span><span style="color: #0000FF;">)</span>
<span style="color: #000000;">lines</span><span style="color: #0000FF;">[</span><span style="color: #000000;">i</span><span style="color: #0000FF;">]</span> <span style="color: #0000FF;">=</span> <span style="color: #0000FF;">{</span><span style="color: #000000;">depth</span><span style="color: #0000FF;">,</span><span style="color: #000000;">text</span><span style="color: #0000FF;">}</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">for</span>
<span style="color: #008080;">return</span> <span style="color: #000000;">lines</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">function</span>
<span style="color: #008080;">function</span> <span style="color: #000000;">indent_to_nested</span><span style="color: #0000FF;">(</span><span style="color: #004080;">sequence</span> <span style="color: #000000;">indent</span><span style="color: #0000FF;">,</span> <span style="color: #004080;">integer</span> <span style="color: #000000;">idx</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span> <span style="color: #000000;">level</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span><span style="color: #0000FF;">)</span>
<span style="color: #004080;">sequence</span> <span style="color: #000000;">res</span> <span style="color: #0000FF;">=</span> <span style="color: #0000FF;">{}</span>
<span style="color: #008080;">while</span> <span style="color: #000000;">idx</span><span style="color: #0000FF;"><=</span><span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">indent</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">do</span>
<span style="color: #0000FF;">{</span><span style="color: #004080;">integer</span> <span style="color: #000000;">lvl</span><span style="color: #0000FF;">,</span> <span style="color: #004080;">string</span> <span style="color: #000000;">text</span><span style="color: #0000FF;">}</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">indent</span><span style="color: #0000FF;">[</span><span style="color: #000000;">idx</span><span style="color: #0000FF;">]</span>
<span style="color: #008080;">if</span> <span style="color: #000000;">lvl</span><span style="color: #0000FF;"><</span><span style="color: #000000;">level</span> <span style="color: #008080;">then</span> <span style="color: #008080;">exit</span> <span style="color: #008080;">end</span> <span style="color: #008080;">if</span>
<span style="color: #0000FF;">{</span><span style="color: #004080;">sequence</span> <span style="color: #000000;">children</span><span style="color: #0000FF;">,</span><span style="color: #000000;">idx</span><span style="color: #0000FF;">}</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">indent_to_nested</span><span style="color: #0000FF;">(</span><span style="color: #000000;">indent</span><span style="color: #0000FF;">,</span><span style="color: #000000;">idx</span><span style="color: #0000FF;">+</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span><span style="color: #000000;">level</span><span style="color: #0000FF;">+</span><span style="color: #000000;">1</span><span style="color: #0000FF;">)</span>
<span style="color: #000000;">res</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">append</span><span style="color: #0000FF;">(</span><span style="color: #000000;">res</span><span style="color: #0000FF;">,{</span><span style="color: #000000;">text</span><span style="color: #0000FF;">,</span><span style="color: #000000;">children</span><span style="color: #0000FF;">})</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">while</span>
<span style="color: #008080;">return</span> <span style="color: #0000FF;">{</span><span style="color: #000000;">res</span><span style="color: #0000FF;">,</span><span style="color: #000000;">idx</span><span style="color: #0000FF;">}</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">function</span>
<span style="color: #008080;">function</span> <span style="color: #000000;">nested_to_indent</span><span style="color: #0000FF;">(</span><span style="color: #004080;">sequence</span> <span style="color: #000000;">nested</span><span style="color: #0000FF;">,</span> <span style="color: #004080;">integer</span> <span style="color: #000000;">level</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span><span style="color: #0000FF;">)</span>
<span style="color: #004080;">sequence</span> <span style="color: #000000;">res</span> <span style="color: #0000FF;">=</span> <span style="color: #0000FF;">{}</span>
<span style="color: #008080;">for</span> <span style="color: #000000;">i</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span> <span style="color: #008080;">to</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">nested</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">do</span>
<span style="color: #0000FF;">{</span><span style="color: #004080;">string</span> <span style="color: #000000;">text</span><span style="color: #0000FF;">,</span> <span style="color: #004080;">sequence</span> <span style="color: #000000;">children</span><span style="color: #0000FF;">}</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">nested</span><span style="color: #0000FF;">[</span><span style="color: #000000;">i</span><span style="color: #0000FF;">]</span>
<span style="color: #000000;">res</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">append</span><span style="color: #0000FF;">(</span><span style="color: #000000;">res</span><span style="color: #0000FF;">,{</span><span style="color: #000000;">level</span><span style="color: #0000FF;">,</span><span style="color: #000000;">text</span><span style="color: #0000FF;">})</span>
<span style="color: #000000;">res</span> <span style="color: #0000FF;">&=</span> <span style="color: #000000;">nested_to_indent</span><span style="color: #0000FF;">(</span><span style="color: #000000;">children</span><span style="color: #0000FF;">,</span><span style="color: #000000;">level</span><span style="color: #0000FF;">+</span><span style="color: #000000;">1</span><span style="color: #0000FF;">)</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">for</span>
<span style="color: #008080;">return</span> <span style="color: #000000;">res</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">function</span>
<span style="color: #008080;">constant</span> <span style="color: #000000;">text</span> <span style="color: #0000FF;">=</span> <span style="color: #008000;">"""
RosettaCode
encourages
code
diversity
comparison
discourages
emphasising execution speed
code-golf.io
encourages
golfing
discourages
comparison"""</span>
<span style="color: #004080;">sequence</span> <span style="color: #000000;">indent</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">text_to_indent</span><span style="color: #0000FF;">(</span><span style="color: #000000;">text</span><span style="color: #0000FF;">),</span>
<span style="color: #000000;">nested</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">indent_to_nested</span><span style="color: #0000FF;">(</span><span style="color: #000000;">indent</span><span style="color: #0000FF;">)[</span><span style="color: #000000;">1</span><span style="color: #0000FF;">],</span>
<span style="color: #000000;">n2ichk</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">nested_to_indent</span><span style="color: #0000FF;">(</span><span style="color: #000000;">nested</span><span style="color: #0000FF;">)</span>
<span style="color: #7060A8;">puts</span><span style="color: #0000FF;">(</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span><span style="color: #008000;">"Indent form:\n"</span><span style="color: #0000FF;">)</span>
<span style="color: #7060A8;">pp</span><span style="color: #0000FF;">(</span><span style="color: #000000;">indent</span><span style="color: #0000FF;">,{</span><span style="color: #000000;">pp_Nest</span><span style="color: #0000FF;">,</span><span style="color: #000000;">1</span><span style="color: #0000FF;">})</span>
<span style="color: #7060A8;">puts</span><span style="color: #0000FF;">(</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span><span style="color: #008000;">"\nNested form:\n"</span><span style="color: #0000FF;">)</span>
<span style="color: #7060A8;">pp</span><span style="color: #0000FF;">(</span><span style="color: #000000;">nested</span><span style="color: #0000FF;">,{</span><span style="color: #000000;">pp_Nest</span><span style="color: #0000FF;">,</span><span style="color: #000000;">8</span><span style="color: #0000FF;">})</span>
<span style="color: #7060A8;">printf</span><span style="color: #0000FF;">(</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span><span style="color: #008000;">"\nNested to indent:%s\n"</span><span style="color: #0000FF;">,{</span><span style="color: #008080;">iff</span><span style="color: #0000FF;">(</span><span style="color: #000000;">n2ichk</span><span style="color: #0000FF;">==</span><span style="color: #000000;">indent</span><span style="color: #0000FF;">?</span><span style="color: #008000;">"same"</span><span style="color: #0000FF;">:</span><span style="color: #008000;">"***ERROR***"</span><span style="color: #0000FF;">)})</span>
<!--</syntaxhighlight>-->
{{out}}
<pre>
Indent form:
{{1, `RosettaCode`},
{2, `encourages`},
{3, `code`},
{4, `diversity`},
{4, `comparison`},
{2, `discourages`},
{3, `emphasising execution speed`},
{1, `code-golf.io`},
{2, `encourages`},
{3, `golfing`},
{2, `discourages`},
{3, `comparison`}}
 
Nested form:
{{`RosettaCode`,
{{`encourages`,
{{`code`,
{{`diversity`,
{}},
{`comparison`,
{}}}}}},
{`discourages`,
{{`emphasising execution speed`,
{}}}}}},
{`code-golf.io`,
{{`encourages`,
{{`golfing`,
{}}}},
{`discourages`,
{{`comparison`,
{}}}}}}}
 
Nested to indent:same
</pre>
You can also strictly enforce these structures, which is obviously useful for debugging.<br>
Admittedly this is somewhat more tedious, but at the same time infinitely more flexible and powerful than a "plain old struct".
<!--<syntaxhighlight lang="phix">-->
<span style="color: #008080;">type</span> <span style="color: #000000;">indent_struct</span><span style="color: #0000FF;">(</span><span style="color: #004080;">object</span> <span style="color: #000000;">o</span><span style="color: #0000FF;">)</span>
<span style="color: #008080;">if</span> <span style="color: #004080;">sequence</span><span style="color: #0000FF;">(</span><span style="color: #000000;">o</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">then</span>
<span style="color: #008080;">for</span> <span style="color: #000000;">i</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span> <span style="color: #008080;">to</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">o</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">do</span>
<span style="color: #004080;">object</span> <span style="color: #000000;">oi</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">o</span><span style="color: #0000FF;">[</span><span style="color: #000000;">i</span><span style="color: #0000FF;">]</span>
<span style="color: #008080;">if</span> <span style="color: #008080;">not</span> <span style="color: #004080;">sequence</span><span style="color: #0000FF;">(</span><span style="color: #000000;">oi</span><span style="color: #0000FF;">)</span>
<span style="color: #008080;">or</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">oi</span><span style="color: #0000FF;">)!=</span><span style="color: #000000;">2</span>
<span style="color: #008080;">or</span> <span style="color: #008080;">not</span> <span style="color: #004080;">integer</span><span style="color: #0000FF;">(</span><span style="color: #000000;">oi</span><span style="color: #0000FF;">[</span><span style="color: #000000;">1</span><span style="color: #0000FF;">])</span>
<span style="color: #008080;">or</span> <span style="color: #008080;">not</span> <span style="color: #004080;">string</span><span style="color: #0000FF;">(</span><span style="color: #000000;">oi</span><span style="color: #0000FF;">[</span><span style="color: #000000;">2</span><span style="color: #0000FF;">])</span> <span style="color: #008080;">then</span>
<span style="color: #008080;">return</span> <span style="color: #004600;">false</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">if</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">for</span>
<span style="color: #008080;">return</span> <span style="color: #004600;">true</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">if</span>
<span style="color: #008080;">return</span> <span style="color: #004600;">false</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">type</span>
<span style="color: #008080;">type</span> <span style="color: #000000;">nested_struct</span><span style="color: #0000FF;">(</span><span style="color: #004080;">object</span> <span style="color: #000000;">o</span><span style="color: #0000FF;">)</span>
<span style="color: #008080;">if</span> <span style="color: #004080;">sequence</span><span style="color: #0000FF;">(</span><span style="color: #000000;">o</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">then</span>
<span style="color: #008080;">for</span> <span style="color: #000000;">i</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span> <span style="color: #008080;">to</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">o</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">do</span>
<span style="color: #004080;">object</span> <span style="color: #000000;">oi</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">o</span><span style="color: #0000FF;">[</span><span style="color: #000000;">i</span><span style="color: #0000FF;">]</span>
<span style="color: #008080;">if</span> <span style="color: #008080;">not</span> <span style="color: #004080;">sequence</span><span style="color: #0000FF;">(</span><span style="color: #000000;">oi</span><span style="color: #0000FF;">)</span>
<span style="color: #008080;">or</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">oi</span><span style="color: #0000FF;">)!=</span><span style="color: #000000;">2</span>
<span style="color: #008080;">or</span> <span style="color: #008080;">not</span> <span style="color: #004080;">string</span><span style="color: #0000FF;">(</span><span style="color: #000000;">oi</span><span style="color: #0000FF;">[</span><span style="color: #000000;">1</span><span style="color: #0000FF;">])</span>
<span style="color: #008080;">or</span> <span style="color: #008080;">not</span> <span style="color: #000000;">nested_struct</span><span style="color: #0000FF;">(</span><span style="color: #000000;">oi</span><span style="color: #0000FF;">[</span><span style="color: #000000;">2</span><span style="color: #0000FF;">])</span> <span style="color: #008080;">then</span>
<span style="color: #008080;">return</span> <span style="color: #004600;">false</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">if</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">for</span>
<span style="color: #008080;">return</span> <span style="color: #004600;">true</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">if</span>
<span style="color: #008080;">return</span> <span style="color: #004600;">false</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">type</span>
<span style="color: #000080;font-style:italic;">-- and as above except:</span>
<span style="color: #008080;">function</span> <span style="color: #000000;">indent_to_nested</span><span style="color: #0000FF;">(</span><span style="color: #000000;">indent_struct</span> <span style="color: #000000;">indent</span><span style="color: #0000FF;">,</span> <span style="color: #004080;">integer</span> <span style="color: #000000;">idx</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span> <span style="color: #000000;">level</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span><span style="color: #0000FF;">)</span>
<span style="color: #008080;">function</span> <span style="color: #000000;">nested_to_indent</span><span style="color: #0000FF;">(</span><span style="color: #000000;">nested_struct</span> <span style="color: #000000;">nested</span><span style="color: #0000FF;">,</span> <span style="color: #004080;">integer</span> <span style="color: #000000;">level</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span><span style="color: #0000FF;">)</span>
<span style="color: #000080;font-style:italic;">-- also make the output sequences better typed:</span>
<span style="color: #000000;">indent_struct</span> <span style="color: #000000;">indent</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">text_to_indent</span><span style="color: #0000FF;">(</span><span style="color: #000000;">text</span><span style="color: #0000FF;">)</span>
<span style="color: #000000;">nested_struct</span> <span style="color: #000000;">nested</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">indent_to_nested</span><span style="color: #0000FF;">(</span><span style="color: #000000;">indent</span><span style="color: #0000FF;">)[</span><span style="color: #000000;">1</span><span style="color: #0000FF;">]</span>
<span style="color: #000000;">indent_struct</span> <span style="color: #000000;">r2ichk</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">nested_to_indent</span><span style="color: #0000FF;">(</span><span style="color: #000000;">nested</span><span style="color: #0000FF;">)</span>
<!--</syntaxhighlight>-->
 
=={{header|Python}}==
Just arranges the standard lists and tuples for the datastructures allowing pprint to show the different arrangement of storage.
 
<langsyntaxhighlight lang="python">from pprint import pprint as pp
 
def to_indent(node, depth=0, flat=None):
Line 204 ⟶ 1,473:
 
if nest != as_nest:
print("Whoops round-trip issues")</langsyntaxhighlight>
 
{{out}}
Line 233 ⟶ 1,502:
('mocks',
[('trolling', [])])])</pre>
 
=={{header|Raku}}==
(formerly Perl 6)
{{works with|Rakudo|2020.08.1}}
Code golf is a entertaining passtime, even if it isn't appropriate for this site. To a large extent, I agree with [[User:Hout|Hout]], I am not really on board with mocking anybody, especially espousing it as an official RosettaCode position. So, feel free to mark this incorrect.
 
<syntaxhighlight lang="raku" line>#`(
Sort of vague as to what we are trying to accomplish here. If we are just
trying to transform from one format to another, probably easiest to just
perform string manipulations.
)
 
my $level = ' ';
 
my $trees = q:to/END/;
RosettaCode
encourages
code
diversity
comparison
discourages
golfing
trolling
emphasising execution speed
code-golf.io
encourages
golfing
discourages
comparison
END
 
sub nested-to-indent { $^str.subst: / ^^ ($($level))* /, -> $/ { "{+$0} " }, :g }
sub indent-to-nested { $^str.subst: / ^^ (\d+) \s* /, -> $/ { "{$level x +$0}" }, :g }
 
say $trees;
say my $indent = $trees.&nested-to-indent;
say my $nest = $indent.&indent-to-nested;
 
use Test;
is($trees, $nest, 'Round-trip equals original');
 
#`(
If, on the other hand, we want perform more complex transformations; better to
load it into a native data structure which will then allow us to manipulate it
however we like.
)
 
# Import outline paragraph into native data structure
sub import (Str $trees, $level = ' ') {
my $forest;
my $last = -Inf;
 
for $trees.lines -> $branch {
$branch ~~ / ($($level))* /;
my $this = +$0;
$forest ~= do {
given $this cmp $last {
when More { "\['{esc $branch.trim}', " }
when Same { "'{esc $branch.trim}', " }
when Less { "{']' x $last - $this}, '{esc $branch.trim}', " }
}
}
$last = $this;
}
 
sub esc { $^s.subst( /(<['\\]>)/, -> $/ { "\\$0" }, :g) }
 
$forest ~= ']' x 1 + $last;
$forest.EVAL;
}
 
my $forest = import $trees;
 
say "\nNative data structure:\n", $forest.raku;
 
{
use JSON::Fast;
say "\nJSON:\n", $forest.&to-json;
}
 
{
use YAML;
say "\nYAML:\n", $forest.&dump;
}</syntaxhighlight>
{{out}}
<pre>RosettaCode
encourages
code
diversity
comparison
discourages
golfing
trolling
emphasising execution speed
code-golf.io
encourages
golfing
discourages
comparison
 
0 RosettaCode
1 encourages
2 code
3 diversity
3 comparison
1 discourages
2 golfing
2 trolling
2 emphasising execution speed
0 code-golf.io
1 encourages
2 golfing
1 discourages
2 comparison
 
RosettaCode
encourages
code
diversity
comparison
discourages
golfing
trolling
emphasising execution speed
code-golf.io
encourages
golfing
discourages
comparison
 
ok 1 - Round-trip equals original
 
Native data structure:
$["RosettaCode", ["encourages", ["code", ["diversity", "comparison"]], "discourages", ["golfing", "trolling", "emphasising execution speed"]], "code-golf.io", ["encourages", ["golfing"], "discourages", ["comparison"]]]
 
JSON:
[
"RosettaCode",
[
"encourages",
[
"code",
[
"diversity",
"comparison"
]
],
"discourages",
[
"golfing",
"trolling",
"emphasising execution speed"
]
],
"code-golf.io",
[
"encourages",
[
"golfing"
],
"discourages",
[
"comparison"
]
]
]
 
YAML:
---
- RosettaCode
- - encourages
- - code
- - diversity
- comparison
- discourages
- - golfing
- trolling
- emphasising execution speed
- code-golf.io
- - encourages
- - golfing
- discourages
- - comparison
...</pre>
 
=={{header|Wren}}==
{{trans|Go}}
{{libheader|Wren-dynamic}}
{{libheader|Wren-fmt}}
<syntaxhighlight lang="wren">import "./dynamic" for Struct
import "./fmt" for Fmt
 
var NNode = Struct.create("NNode", ["name", "children"])
var INode = Struct.create("INode", ["level", "name"])
 
var sw = ""
 
var printNest // recursive
printNest = Fn.new { |n, level|
if (level == 0) sw = sw + "\n==Nest form==\n\n"
sw = sw + Fmt.swrite("$0s$s\n", " " * level, n.name)
for (c in n.children) {
sw = sw + (" " * (level + 1))
printNest.call(c, level+1)
}
}
 
var toNest // recursive
toNest = Fn.new { |iNodes, start, level, n|
if (level == 0) n.name = iNodes[0].name
var i = start + 1
while (i < iNodes.count) {
if (iNodes[i].level == level + 1) {
var c = NNode.new(iNodes[i].name, [])
toNest.call(iNodes, i, level+1, c)
n.children.add(c)
} else if (iNodes[i].level <= level) return
i = i + 1
}
}
 
var printIndent = Fn.new { |iNodes|
sw = sw + "\n==Indent form==\n\n"
for (n in iNodes) sw = sw + Fmt.swrite("$d $s\n", n.level, n.name)
}
 
var toIndent // recursive
toIndent = Fn.new { |n, level, iNodes|
iNodes.add(INode.new(level, n.name))
for (c in n.children) toIndent.call(c, level+1, iNodes)
}
 
var n1 = NNode.new("RosettaCode", [])
var n2 = NNode.new("rocks", [NNode.new("code", []), NNode.new("comparison", []), NNode.new("wiki", [])])
var n3 = NNode.new("mocks", [NNode.new("trolling", [])])
n1.children.add(n2)
n1.children.add(n3)
 
printNest.call(n1, 0)
var s1 = sw
System.print(s1)
 
var iNodes = []
toIndent.call(n1, 0, iNodes)
sw = ""
printIndent.call(iNodes)
System.print(sw)
 
var n = NNode.new("", [])
toNest.call(iNodes, 0, 0, n)
sw = ""
printNest.call(n, 0)
var s2 = sw
System.print(s2)
 
System.print("\nRound trip test satisfied? %(s1 == s2)")</syntaxhighlight>
 
{{out}}
<pre>
==Nest form==
 
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
 
 
==Indent form==
 
0 RosettaCode
1 rocks
2 code
2 comparison
2 wiki
1 mocks
2 trolling
 
 
==Nest form==
 
RosettaCode
rocks
code
comparison
wiki
mocks
trolling
 
 
Round trip test satisfied? true
</pre>
 
=={{header|zkl}}==
<syntaxhighlight lang="zkl">fcn nestToIndent(nestTree){
<lang zkl></lang>
fcn(out,node,level){
<lang zkl></lang>
out.append(List(level,node[0])); // (n,name) or ("..",name)
if(node.len()>1){ // (name children), (name, (tree))
level+=1;
foreach child in (node[1,*]){
if(String.isType(child)) out.append(List(level,child));
else self.fcn(out,child,level)
}
}
out
}(List(),nestTree,0)
}
fcn nestToString(nestTree,dot="."){
fcn(out,dot,node,level){
out.writeln(dot*level,node[0]); // (name)
if(node.len()>1){ // (name children), (name, (tree))
level+=1;
foreach child in (node[1,*]){
if(String.isType(child)) out.writeln(dot*level,child);
else self.fcn(out,dot,child,level)
}
}
out
}(Data(),dot,nestTree,0).text
}
 
fcn indentToNest(iTree,depth=0,nTree=List()){
while(iTree){ // (n,name)
d, name := iTree[0];
if(d==depth){
nTree.append(name);
iTree.pop(0);
}
else if(d>depth){ // assume can't skip levels down
if(nTree.len()>1 and not List.isType((nm:=nTree[-1]))){
nTree[-1]=(children:=List(nm));
indentToNest(iTree,d,children);
}else{
nTree.append(children:=List(name));
iTree.pop(0);
indentToNest(iTree,d+1,children);
}
}
else break; // d<depth
}
return(nTree)
}
fcn indentToString(indentTree){ indentTree.apply("concat"," ").concat("\n") }</syntaxhighlight>
<syntaxhighlight lang="zkl">tree:=L("RosettaCode",
L("rocks","code","comparison","wiki"),
L("mocks","golfing") );
 
println("Nest tree internal format:\n",tree.toString(*,*));
println("Formated:\n",nestToString(tree));
 
indentTree:=nestToIndent(tree);
println("To indent format:\n",indentToString(indentTree));
 
nestTree:=indentToNest(indentTree);
println("\nIndent to nested format:\n",nestTree);
println("Is this tree the same as what we started with? ",nestTree==tree);</syntaxhighlight>
{{out}}
<pre>
Nest tree internal format:
L("RosettaCode",L("rocks","code","comparison","wiki"),L("mocks","golfing"))
Formated:
RosettaCode
.rocks
..code
..comparison
..wiki
.mocks
..golfing
 
To indent format:
0 RosettaCode
1 rocks
2 code
2 comparison
2 wiki
1 mocks
2 golfing
 
Indent to nested format:
L("RosettaCode",L("rocks","code","comparison","wiki"),L("mocks","golfing"))
Is this tree the same as what we started with? True
</pre>
I'm choosing to only allow one root per tree/forest so the Raku example is coded differently:
<syntaxhighlight lang="zkl">rakutrees:=L(
L("RosettaCode",
L("encourages",
L("code",
"diversity","comparison")),
L("discourages",
"golfing","trolling","emphasising execution speed"),
),
L("code-golf.io",
L("encourages","golfing"),
L("discourages","comparison"),
)
);
println(rakutrees.apply(nestToString).concat());
iTrees := rakutrees.apply(nestToIndent);
println(iTrees.apply(indentToString).concat("\n"));
(iTrees.apply(indentToNest)==rakutrees).println();</syntaxhighlight>
{{out}}
<pre style="height:40ex">
RosettaCode
encourages
code
diversity
comparison
discourages
golfing
trolling
emphasising execution speed
code-golf.io
encourages
golfing
discourages
comparison
 
0 RosettaCode
1 encourages
2 code
3 diversity
3 comparison
1 discourages
2 golfing
2 trolling
2 emphasising execution speed
0 code-golf.io
1 encourages
2 golfing
1 discourages
2 comparison
True
</pre>
891

edits