I wish to print a binary tree in Newick format, showing each node's distance to its parent. At the moment I haven't had an issue with the following code, which uses regular recursion, but a tree too deep may produce a stack overflow.
(defn tree->newick
[tree]
(let [{:keys [id children to-parent]} tree
dist (double to-parent)] ; to-parent may be a rational
(if children
(str "(" (tree->newick (first children))
"," (tree->newick (second children))
"):" dist)
(str (name id) ":" dist))))
(def example {:id nil :to-parent 0.0
:children [{:id nil :to-parent 0.5
:children [{:id "A" :to-parent 0.3 :children nil}
{:id "B" :to-parent 0.2 :children nil}]}
{:id "C" :to-parent 0.8 :children nil}]})
(tree->newick example)
;=> "((A:0.3,B:0.2):0.5,C:0.8):0.0"
(def linear-tree (->> {:id "bottom" :to-parent 0.1 :children nil}
(iterate #(hash-map :id nil :to-parent 0.1
:children [% {:id "side" :to-parent 0.1 :children nil}]))
(take 10000)
last))
(tree->newick linear-tree)
;=> StackOverflowError
The problem I've found with current utilities, such as tree-seq and clojure.walk, is that I have to visit an inner node more than once, to interpose the comma and close the bracket. I've used clojure.zip, but didn't manage to write a lazy/tail-recursive implementation, as I would need to store for each inner node how many times they were already visited.
Here's a version that works on your linear-tree example. It's a direct conversion of your implementation with two changes: it uses continuation passing style and the trampoline.
(defn tree->newick
([tree]
(trampoline tree->newick tree identity))
([tree cont]
(let [{:keys [id children to-parent]} tree
dist (double to-parent)] ; to-parent may be a rational
(if children
(fn []
(tree->newick
(first children)
(fn [s1] (fn []
(tree->newick
(second children)
(fn [s2] (cont (str "(" s1 "," s2 "):" dist))))))))
(cont (str (name id) ":" dist))))))
Edit: added pattern matching to allow calling the function in a simple way.
Edit 2: I noticed that I made mistake. The problem is that I did take the fact that Clojure doesn't optimize tail calls only partially into account.
The core idea of my solution is the transformation into continuation passing style so the recursive calls can be moved into tail position (i.e. instead of returning their result, the recursive calls pass it to the continuation as argument).
Then I hand-optimized the recursive calls by making them use the trampoline. What I forgot to consider is that the calls of the continuations - which are not recursive calls but also in tail position - need to be optimized, too, because the tail calls can be a very long chain of closures, so that when the function finally evaluates them, it becomes a long chain of calls.
This problem did not materialize with the the test data linear-tree because the continuation for the first child returns to the trampoline to process recursive call for the second child. But if linear-tree is changed so that it uses the second child of every node to build the linear tree instead of the first child, this does again cause a stack overflow.
So the calls of the continuations need to return to the trampoline, too. (Actually, the call in the no children base case does not, because it will happen at most once before returning to trampoline, and the same will then be true for the second recursive call.) So here's an implementation that does take this into consideration and should use only constant stack space on all inputs:
(defn tree->newick
([tree]
(trampoline tree->newick tree identity))
([tree cont]
(let [{:keys [id children to-parent]} tree
dist (double to-parent)] ; to-parent may be a rational
(if children
(fn [] (tree->newick
(first children)
(fn [s1] (tree->newick
(second children)
(fn [s2] #(cont (str "(" s1 "," s2 "):" dist)))))))
(cont (str (name id) ":" dist))))))
Related
My try:
(defn inc-by-f [v]
map #(+ (first v) %) v)
EDIT
(The original question was stupid; I missed the parenthesis. I am still leaving the question, so that perhaps I learn some new ways to deal with it.)
(defn inc-by-f [v]
(map #(+ (first v) %) v))
What other cool “Clojure” ways to achieve the desired result?
"Cooler" way (answered later than https://stackoverflow.com/a/62536870/823470 by Bob Jarvis):
(defn inc-by-f
[[v1 :as v]]
(map (partial + v1) v))
This uses
sequential destructuring to extract the first element of the input vector while still maintaining a reference to the entire vector using :as
partial to avoid the need for an anonymous function literal, which increases readability in some peoples' opinion (count me in!)
Note that the vector destructuring is only useful if the increment value is in a place that is easily accessible by destructuring. It could work if the value was the "2nd in the vector" ([_ v2 :as v]), for example, but not if the value was "the maximum element in the vector". In that case, the max would have to be obtained explicitly, e.g.
(defn inc-by-max
[v]
(map (partial + (apply max v)) v))
Also note that anonymous functions are evaluated on each call, unlike partial which is handed all its arguments and then those no longer need to be evaluated. In other words, if we take the first element of a 1000-element v inside the anonymous function, that will result in 1000 calls to first, instead of just one if we get the first element and pass it to partial. Demonstration:
user=> (dorun (map #(+ (do (println "called") 42) %) (range 3)))
called
called
called
=> nil
user=> (dorun (map (partial + (do (println "called") 42)) (range 3)))
called
=> nil
You're missing parentheses around the map invocation. The following works as you expect:
(defn inc-by-f [v]
(map #(+ (first v) %) v))
For a given tree I would like to sum the depth of each node and calculate that recursively (so not with map/flatten/sum).
Is there a way to do that with recur or do I need to use a zipper in this case?
recur is for tail recursion, meaning if you could do it with normal recursion, where the return value is exactly what a single recursive call would return, then you can use it.
Most functions on trees cannot be written in a straightforward way when restricted to using only tail recursion. Normal recursive calls are much more straightforward, and as long as the tree depth is not thousands of levels deep, then normal recursive calls are just fine in Clojure.
The reason you may have found recommendations against using normal recursive calls in Clojure is for cases when the call stack could grow to tens or hundreds of thousands of calls deep, e.g. a recursive call one level deep for each element of a sequence that could be tens or hundreds of thousands of elements long. That would exceed the default maximum call stack depth limits of many run-time systems.
Using normal stack consuming recursion you can accomplish this pretty easily, by doing a depth-first traversal and summing the depth on the way back out.
(defn sum-depths
([tree]
(sum-depths tree 0))
([node depth]
(if-not (vector? node)
depth
(do
(apply
+
(for [child-node (second node)]
(sum-depths child-node (inc depth))))))))
(sum-depths [:root
[:a1
[:b1
[:a2 :b2]]
:c1]])
;; => 6
(sum-depths ["COM"
[["B"
[["C"
[["D"
[["E"
["F"
["J"
[["K"
["L"]]]]]]
"I"]]]]
["G"
["H"]]]]]])
;; => 19
The details depend a little bit on how you model your tree, so the above assumes that a node is either a vector pair where the first element is the value and the second element is a vector of children nodes, or if it is a leaf node then it's not a vector.
So a leaf node is anything that's not a vector.
And a node with children is a vector of form: [value [child1 child2 ...]
And here I assumed you wanted to sum the depth of all leaf nodes. Since I see from your answer, that your example gives 42, I'm now thinking you meant the sum of the depth of every node, not just leaves, if so it only takes one extra line of code to do so:
(defn sum-depths
([tree]
(sum-depths tree 0))
([node depth]
(if-not (vector? node)
depth
(do
(apply
+
depth
(for [child-node (second node)]
(sum-depths child-node (inc depth))))))))
(sum-depths [:root
[:a1
[:b1
[:a2 :b2]]
:c1]])
;; => 7
(sum-depths ["COM"
[["B"
[["C"
[["D"
[["E"
["F"
["J"
[["K"
["L"]]]]]]
"I"]]]]
["G"
["H"]]]]]])
;; => 42
And like your own answer showed, this particular algorithm can be solved without a stack as well, by doing a level order traversal (aka breadth-first traversal) of the tree. Here it is working on my tree data-structure (similar strategy then your own answer otherwise):
(defn sum-depths [tree]
(loop [children (second tree) depth 0 total 0]
(if (empty? children)
total
(let [child-depth (inc depth)
level-total (* (count children) child-depth)]
(recur (into [] (comp (filter vector?) (mapcat second)) children)
child-depth
(+ total level-total))))))
(sum-depths [:root
[:a1
[:b1
[:a2 :b2]]
:c1]])
;; => 7
(sum-depths ["COM"
[["B"
[["C"
[["D"
[["E"
["F"
["J"
[["K"
["L"]]]]]]
"I"]]]]
["G"
["H"]]]]]])
;; => 42
And for completeness, I also want to show how you can do a depth-first recursive traversal using core.async instead of the function call stack in order to be able to traverse trees that would cause a StackOverFlow otherwise, but still using a stack based recursive depth-first traversal instead of an iterative one. As an aside, there exists some non stack consuming O(1) space depth-first traversals as well, using threaded trees (Morris algorithm) or tree transformations, but I won't show those as I'm not super familiar with them and I believe they only work on binary trees.
First, let's construct a degenerate tree of depth 10000 which causes a StackOverFlow when run against our original stack-recursive sum-depths:
(def tree
(loop [i 0 t [:a [:b]]]
(if (< i 10000)
(recur (inc i)
[:a [t]])
t)))
(defn sum-depths
([tree]
(sum-depths tree 0))
([node depth]
(if-not (vector? node)
depth
(do
(apply
+
depth
(for [child-node (second node)]
(sum-depths child-node (inc depth))))))))
(sum-depths tree)
;; => java.lang.StackOverflowError
If it works on your machine, try increasing 10000 to something even bigger.
Now we rewrite it to use core.async instead:
(require '[clojure.core.async :as async])
(defmacro for* [[element-sym coll] & body]
`(loop [acc# [] coll# ~coll]
(if-let [~element-sym (first coll#)]
(recur (conj acc# (do ~#body)) (next coll#))
acc#)))
(def tree
(loop [i 0 t [:a [:b]]]
(if (< i 10000)
(recur (inc i)
[:a [t]])
t)))
(defn sum-depths
([tree]
(async/<!! (sum-depths tree 0)))
([node depth]
(async/go
(if-not (vector? node)
depth
(do
(apply
+
depth
(for* [child-node (second node)]
(async/<!
(sum-depths child-node (inc depth))))))))))
;; => (sum-depths tree)
50015001
It is relatively easy to rewrite a stack-recursive algorithm to use core.async instead of the call stack, and thus make it so it isn't at risk of causing a StackOverFlow in the case of large inputs. Just wrap it in a go block, and wrap the recursive calls in a <! and the whole algorithm in a <!!. The only tricky part is that core.async cannot cross function boundaries, which is why the for* macro is used above. The normal Clojure for macro crosses function boundaries internally, and thus we can't use <! inside it. By rewriting it to not do so, we can use <! inside it.
Now for this particular algorithm, the tail-recursive variant using loop/recur is probably best, but I wanted to show this technique of using core.async for posterity, since it can be useful in other cases where there isn't a trivial tail-recursive implementation.
i would also propose this one, which is kinda straightforward:
it uses more or less the same approach, as tail recursive flatten does:
(defn sum-depth
([data] (sum-depth data 1 0))
([[x & xs :as data] curr res]
(cond (empty? data) res
(coll? x) (recur (concat x [:local/up] xs) (inc curr) res)
(= :local/up x) (recur xs (dec curr) res)
:else (recur xs curr (+ res curr)))))
the trick is that when you encounter the collection at the head of the sequence, you concat it to the rest, adding special indicator that signals the end of branch and level up. It allows you to track the current depth value. Quite simple, and also using one pass.
user> (sum-depth [1 [2 7] [3]])
;;=> 7
user> (sum-depth [1 2 3 [[[[[4]]]]]])
;;=> 9
You can use map/mapcat to walk a tree recursively to produce a lazy-seq (of leaf nodes). If you need depth information, just add it along the way.
(defn leaf-seq
[branch? children root]
(let [walk (fn walk [lvl node]
(if (branch? node)
(->> node
children
(mapcat (partial walk (inc lvl))))
[{:lvl lvl
:leaf node}]))]
(walk 0 root)))
To run:
(->> '((1 2 ((3))) (4))
(leaf-seq seq? identity)
(map :lvl)
(reduce +))
;; => 10
where the depths of each node are:
(->> '((1 2 ((3))) (4))
(leaf-seq seq? identity)
(map :lvl))
;; => (2 2 4 2)
Updates - sum all nodes instead of just leaf nodes
I misread the original requirement and was assuming leaf nodes only. To add the branch node back is easy, we just need to cons it before its child sequence.
(defn node-seq
"Returns all the nodes marked with depth/level"
[branch? children root]
(let [walk (fn walk [lvl node]
(lazy-seq
(cons {:lvl lvl
:node node}
(when (branch? node)
(->> node
children
(mapcat (partial walk (inc lvl))))))))]
(walk 0 root)))
Then we can walk on the hiccup-like tree as before:
(->> ["COM" [["B" [["C" [["D" [["E" [["F"] ["J" [["K" [["L"]]]]]]] ["I"]]]]] ["G" [["H"]]]]]]]
(node-seq #(s/valid? ::branch %) second)
(map :lvl)
(reduce +))
;; => 42
Note: above function uses below helper specs to identify the branch/leaf:
(s/def ::leaf (s/coll-of string? :min-count 1 :max-count 1))
(s/def ::branch (s/cat :tag string? :children (s/coll-of (s/or :leaf ::leaf
:branch ::branch))))
Here's my alternative approach that does use recur:
(defn sum-of-depths
[branches]
(loop [branches branches
cur-depth 0
total-depth 0]
(cond
(empty? branches) total-depth
:else (recur
(mapcat (fn [node] (second node)) branches)
(inc cur-depth)
(+ total-depth (* (count branches) cur-depth))))))
(def tree ["COM" (["B" (["C" (["D" (["E" (["F"] ["J" (["K" (["L"])])])] ["I"])])] ["G" (["H"])])])])
(sum-of-depths [tree]) ; For the first call we have to wrap the tree in a list.
=> 42
You can do this using the Tupelo Forest library. Here is a function to extract information about a tree in Hiccup format. First, think about how we want to use the information for a simple tree with 3 nodes:
(dotest
(hid-count-reset)
(let [td (tree-data [:a
[:b 21]
[:c 39]])]
(is= (grab :paths td) [[1003]
[1003 1001]
[1003 1002]])
(is= (grab :node-hids td) [1003 1001 1002])
(is= (grab :tags td) [:a :b :c])
(is= (grab :depths td) [1 2 2])
(is= (grab :total-depth td) 5) ))
Here is how we calculate the above information:
(ns tst.demo.core
(:use tupelo.forest tupelo.core tupelo.test)
(:require
[schema.core :as s]
[tupelo.schema :as tsk]))
(s/defn tree-data :- tsk/KeyMap
"Returns data about a hiccup tree"
[hiccup :- tsk/Vec]
(with-forest (new-forest)
(let [root-hid (add-tree-hiccup hiccup)
paths (find-paths root-hid [:** :*])
node-hids (mapv xlast paths)
tags (mapv #(grab :tag (hid->node %)) node-hids)
depths (mapv count paths)
total-depth (apply + depths)]
(vals->map paths node-hids tags depths total-depth))))
and an example on a larger Hiccup-format tree:
(dotest
(let [td (tree-data [:a
[:b 21]
[:b 22]
[:b
[:c
[:d
[:e
[:f
[:g 7]
[:h
[:i 9]]]]]]
[:c 32]]
[:c 39]])]
(is= (grab :tags td) [:a :b :b :b :c :d :e :f :g :h :i :c :c])
(is= (grab :depths td) [1 2 2 2 3 4 5 6 7 7 8 3 2])
(is= (grab :total-depth td) 52)))
Don't be afraid of stack size for normal processing. On my computer, the default stack doesn't overflow until you get to a stack depth of over 3900 recursive calls. For a binary tree, just 2^30 is over a billion nodes, and 2^300 is more nodes than the number of protons in the universe (approx).
I've been struggling with a recursion problem and I'm running out of ideas. Basically, I have a tree representation that looks like this:
{1 {:root nil} 2 {:root 1} 3 {:root 1} 4 {:root 2} 5 {:root 1} 6 {:root 4}}
And I have to build a new tree out of the last one which indicates parent/child relationship levels. A valid output would be:
{ 1 [3 1] 2 [1] 3 [] 4 [1] 5 [] 6 [] }
Where each node has an array of a count of items by level of relationship. So node 1 has 3 direct children (2 3 5) and one grandchild (4). Node 2 has only one child (4), node 4 has one direct child (6) and all the others are empty (have no children).
I found some questions like this one that actually helped but aren't exactly what I was looking for. I'm also new to function programming and any help is going to be appreciated.
I'm going to assume that there is an error in your sample output above and that it should really be:
{ 1 [3 1 1] 2 [1 1] 3 [] 4 [1] 5 [] 6 [] }
Your sample output did not account for the fact that 6 is a great-grandchild of 1 and a grandchild of 2.
I'll detail a solution here. We'll start out by writing a function which, given a tree and a vertex in that tree, calculates the path from that vertex to the top of the tree:
(defn path-to-top [tree v]
(if (nil? v)
'()
(cons v (path-to-top tree (:root (get tree v))))))
Next up, let us write a function which takes such a path from the vertex to the top of the tree and associates with each vertex on the distance of that vertex from the starting vertex:
(defn steps-indexed-path
([upward-path steps]
(if (= upward-path '())
'()
(cons [(first upward-path) steps] (steps-indexed-path (rest upward-path) (+ steps 1)))))
([upward-path]
(steps-indexed-path upward-path 0)))
Where the first function returned a list of vertices, this function returns a list of vectors in which the first entry is a vertex and the second entry is the number of steps from the first vertex on the path to the given vertex.
Alright, when we apply this function to each of the vertices in the tree, we will have (in some nested form) for each vertex v and for each descendant w of v the data [v <# steps from v to w>]. For each of these data, we should add 1 to the <# steps from v to w> component of the vector associated with v in our final solution. Before we move to the vector stage, let us just associate levels with counts:
(defn count-descendants [tree]
(let [markers (reduce concat '() (map steps-indexed-path (map (partial path-to-top tree) (keys tree))))]
(reduce (fn [counter [vertex generation]] (assoc counter vertex (assoc (get counter vertex {}) generation (+ (get (get counter vertex {}) generation 0) 1)))) {} markers)))
This produces a hash-map whose keys are the vertices of v and such that the value corresponding to each vertex v is another hash-map in which the keys are the different possible generations of descendants of that vertex in the tree, and the values are the number of descendants at each generation.
All we have to do now is turn the output of the previous function into the format specified by you:
(defn sanitize-descendant-counts [association]
(let [max-depth (apply max (keys association))]
(map (fn [i] (get association i 0)) (range 1 (+ max-depth 1)))))
(defn solve-problem [tree]
(let [descendant-counts (count-descendants tree)]
(apply merge (map (fn [v] (hash-map v (vec (sanitize-descendant-counts (get descendant-counts v))))) (keys descendant-counts)))))
This is what I get as output when I run this code on your example:
{1 [3 1 1], 4 [1], 6 [], 3 [], 2 [1 1], 5 []}
You can access all the code here, including what you need to run on your example. Hope that helps!
I will try to outline a possible approach, stressing the recursion core, and glossing over smaller details. There are quite a few of those smaller details, and some of them aren't exactly trivial, but they have nothing to do with the recursion itself, and would just clutter the answer.
Let's abstract from the details of your tree representation. Think about a tree as a collection of nodes, where each node may be either a leaf (no children,) or a branch otherwise. Assume we have two functions branch? and children. Either receives one parameter - a node. branch? is a predicate with an obvious meaning, children returns a sequence of children of the node. (It is the same contract as expected by tree-seq core function.) I leave it to you to code branch? and children. (You may want to change your tree representation to make it easier to code these functions.)
Let's try to create a function levels that given a node will return a sequence of number of descendants by levels - children, grandchildren and so on. So we would expect for your tree
(levels 1)
;; => (3 1 1)
(levels 2)
;; => (1 1)
(You got a typo, by the way. Node 1 has a grand-grandchild - it's 6)
And here's the core - levels:
(defn levels
[node]
(if (branch? node)
(cons (count (children node)) (sum-up-levels (map levels (children node))))
[]))
This is the meat of the recursion. The base case is the leaf - when branch? returns false we know there are no children, so the levels are empty - []. Otherwise, we count the children and cons that number (i.e. add to the list) of the summed up levels below. Summing up means summing the numbers by levels - total number of children, then total number of grandchildren and so on. And here we have the recursion - we descend down to the children, invoking levels recursively for every child using map.
The sum-up-levels function is a bit annoying to code. I am leaving so much for you to fill in that I'd probably just give my code of it here (certainly not the shortest possible, but I don't have more time to polish it.)
(defn reduce-through
[f & colls]
(when-let [colls (seq (filter seq colls))]
(cons (reduce f (map first colls))
(apply reduce-through f (map rest colls)))))
(defn sum-up-levels
[levels]
(apply reduce-through + levels))
After having levels defined, it's easy to get the result in the form you need. Try it (a hint - use tree-seq.)
(defn children-depths [parents]
(let [children ; let's first build an inverted index
(reduce-kv (fn [children node {parent :root}]
(update children parent conj node))
{} parents)
depths (fn depths [node]
(if-some [nodes (children node)]
(into [(count nodes)]
; pads and sums
(reduce #(map + (concat %1 (repeat 0)) (depths %2))
nil nodes))
[]))] ; no descendants -> empty
(into {} (for [node (keys parents)] [node (depths node)]))))
=> (children-depths {1 {:root nil} 2 {:root 1} 3 {:root 1} 4 {:root 2} 5 {:root 1} 6 {:root 4}})
{1 [3 1 1], 2 [1 1], 3 [], 4 [1], 5 [], 6 []}
One obvious improvement would be to avoid recomputing depths of children.
How can I create a Clojure zipper for a TRIE, represented by nested maps, were the keys are the letters.?
Something like this:
{\b {\a {\n {\a {\n {\a {'$ '$}}}}}} \a {\n {\a {'$ '$}}}}
Represents a trie with 2 words 'banana' and 'ana'. (If necessary , its possible to make some changes here in maps..)
I've tried to pass map? vals assoc as the 3 functions to the zipper,respectively.
But it doesnt seem to work..
What 3 functions should I use?
And how the insert-into-trie would look like based on the zipper ?
map? vals #(zipmap (keys %1) %2) would do but doesn't support insertion/removal of children (since children are only values, you don't know which key to remove/add).
The map-zipper below does support insertion/removal because nodes are [k v] pairs (except the root which is a map).
(defn map-zipper [m]
(z/zipper
(fn [x] (or (map? x) (map? (nth x 1))))
(fn [x] (seq (if (map? x) x (nth x 1))))
(fn [x children]
(if (map? x)
(into {} children)
(assoc x 1 (into {} children))))
m))
The solution proposed by #cgrant is great, but implicitly describes a tree where all branches and leaf nodes have an associated value (the key in the dictionary) except for the root node that is just a branch without a value.
So, the tree {"/" nil}, is not a tree with a single leaf node, but a tree with an anonymous root branch and a single leaf node with value /.
In practice, this means that every traversal of the tree has to first execute a (zip/down t) in order to descend the root node.
An alternative solution is to explicitly model the root inside the map, that is, only create zippers from maps with a single key at the root. For example: {"/" {"etc/" {"hosts" nil}}}
The zipper can then be implemented with:
(defn map-zipper [map-or-pair]
"Define a zipper data-structure to navigate trees represented as nested dictionaries."
(if (or (and (map? map-or-pair) (= 1 (count map-or-pair))) (and (= 2 (count map-or-pair))))
(let [pair (if (map? map-or-pair) (first (seq map-or-pair)) map-or-pair)]
(zip/zipper
(fn [x] (map? (nth x 1)))
(fn [x] (seq (nth x 1)))
(fn [x children] (assoc x 1 (into {} children)))
pair))
(throw (Exception. "Input must be a map with a single root node or a pair."))))
I have an ANTLR3 AST which I need to traverse using a post-order, depth-first traversal which I have implemented as roughly the following Clojure:
(defn walk-tree [^CommonTree node]
(if (zero? (.getChildCount node))
(read-string (.getText node))
(execute-node
(map-action node)
(map walk-tree (.getChildren node)))))))
I would like to convert this to tail recursion using loop...recur, but I haven't been able to figure out how to effectively use an explicit stack to do this since I need a post-order traversal.
Instead of producing a tail recursive solution which traverses the tree and visits each node, you could produce a lazy sequence of the depth first traversal using the tree-seq function and then get the text out of each object in the traversal. Lazy sequences never blow the stack because they store all the state required to produce the next item in the sequence in the heap. They are very often used instead of recursive solutions like this where loop and recur are more diffacult.
I don't know what your tree looks like though a typical answer would look something like this. You would need to play with the "Has Children" "list of children" functions
(map #(.getText %) ;; Has Children? List of Children Input Tree
(tree-seq #(> (.getChildCount #) 0) #(.getChildren %) my-antlr-ast))
If tree-seq does not suit your needs there are other ways to produce a lazy sequence from a tree. Look at the zipper library next.
As you mention, the only way to implement this using tail recursion is to switch to using an explicit stack. One possible approach is to convert the tree structure into a stack structure that is essentially a Reverse Polish notation representation of the tree (using a loop and an intermediate stack to accomplish this). You would then use another loop to traverse the stack and build up your result.
Here's a sample program that I wrote to accomplish this, using the Java code at postorder using tail recursion as an inspiration.
(def op-map {'+ +, '- -, '* *, '/ /})
;; Convert the tree to a linear, postfix notation stack
(defn build-traversal [tree]
(loop [stack [tree] traversal []]
(if (empty? stack)
traversal
(let [e (peek stack)
s (pop stack)]
(if (seq? e)
(recur (into s (rest e))
(conj traversal {:op (first e) :count (count (rest e))}))
(recur s (conj traversal {:arg e})))))))
;; Pop the last n items off the stack, returning a vector with the remaining
;; stack and a list of the last n items in the order they were added to
;; the stack
(defn pop-n [stack n]
(loop [i n s stack t '()]
(if (= i 0)
[s t]
(recur (dec i) (pop s) (conj t (peek s))))))
;; Evaluate the operations in a depth-first manner, using a temporary stack
;; to hold intermediate results.
(defn eval-traversal [traversal]
(loop [op-stack traversal arg-stack []]
(if (empty? op-stack)
(peek arg-stack)
(let [o (peek op-stack)
s (pop op-stack)]
(if-let [a (:arg o)]
(recur s (conj arg-stack a))
(let [[args op-args] (pop-n arg-stack (:count o))]
(recur s (conj args (apply (op-map (:op o)) op-args)))))))))
(defn eval-tree [tree] (-> tree build-traversal eval-traversal))
You can call it as such:
user> (def t '(* (+ 1 2) (- 4 1 2) (/ 6 3)))
#'user/t
user> (eval-tree t)
6
I leave it as an exercise to the reader to convert this to work with a Antlr AST structure ;)
I'm not skilled up on clojure, but I think I understand what you're looking for.
Here's some pseudocode. The stack here in my pseudocode looks like a stateful object, but it's quite feasible to use an immutable one instead. It uses something like O(depth of tree * max children per node) heap.
walk_tree(TreeNode node) {
stack = new Stack<Pair<TreeNode, Boolean>>();
push(Pair(node, True), stack)
walk_tree_aux(stack);
}
walk_tree_aux(Stack<Pair<TreeNode, Boolean>> stack) { -- this should be tail-recursive
if stack is empty, return;
let (topnode, topflag) = pop(stack);
if (topflag is true) {
push Pair(topnode, False) onto stack);
for each child of topnode, in reverse order:
push(Pair(child, True)) onto stack
walk_tree_aux(stack);
} else { -- topflag is false
process(topnode)
walk_tree_aux(stack);
}
}