@@ -10,7 +10,7 @@ struct InitialState end
1010
1111
1212"""
13- TreeCursor{P,N }
13+ TreeCursor{N,P }
1414
1515Abstract type for tree cursors which when constructed from a node can be used to
1616navigate the entire tree descended from that node.
@@ -25,21 +25,27 @@ Tree nodes which define `children` and have the traits [`StoredParents`](@ref) a
2525[`StoredSiblings`](@ref) satisfy the `TreeCursor` interface, but calling `TreeCursor(node)` on such
2626a node wraps them in a [`TrivialCursor`](@ref) to maintain a consistent interface.
2727
28+ Note that any `TreeCursor` created from a non-cursor node is the root of its own tree, but can be created
29+ from any tree node. For example the cursor created from the tree `[1,[2,3]]` corresponding to node with
30+ value `[2,3]` has no parent and children `2` and `3`. This is because a cursor created this way cannot
31+ infer the iteration state of its siblings. These constructors are still allowed so that users can
32+ run tree algorithms over non-root nodes but they do not permit ascension from the initial node.
33+
2834## Constructors
2935All `TreeCursor`s possess (at least) the following constructors
3036- `T(node)`
3137- `T(parent, node)`
3238
3339In the former case the `TreeCursor` is constructed for the tree of which `node` is the root.
3440"""
35- abstract type TreeCursor{P,N } end
41+ abstract type TreeCursor{N,P } end
3642
3743"""
3844 nodevaluetype(csr::TreeCursor)
3945
4046Get the type of the wrapped node. This should match the return type of [`nodevalue`](@ref).
4147"""
42- nodevaluetype (:: Type{<:TreeCursor{P,N }} ) where {P,N } = N
48+ nodevaluetype (:: Type{<:TreeCursor{N,P }} ) where {N,P } = N
4349nodevaluetype (csr:: TreeCursor ) = nodevaluetype (typeof (csr))
4450
4551"""
@@ -48,13 +54,16 @@ nodevaluetype(csr::TreeCursor) = nodevaluetype(typeof(csr))
4854The return type of `parent(csr)`. For properly constructed `TreeCursor`s this is guaranteed to be another
4955`TreeCursor`.
5056"""
51- parenttype (:: Type{<:TreeCursor{P,N }} ) where {P,N } = P
57+ parenttype (:: Type{<:TreeCursor{N,P }} ) where {N,P } = P
5258parenttype (csr:: TreeCursor ) = parenttype (typeof (csr))
5359
5460# this is a fallback and may not always be the case
55- Base. IteratorSize (:: Type{<:TreeCursor{P,N}} ) where {P,N} = IteratorSize (childtype (N))
61+ Base. IteratorSize (:: Type{<:TreeCursor{N,P}} ) where {N,P} = Base. IteratorSize (childrentype (N))
62+
63+ Base. length (tc:: TreeCursor ) = (length ∘ children ∘ nodevalue)(tc)
5664
57- Base. length (tc:: TreeCursor ) = (length ∘ children ∘ nodevalue)(csr)
65+ # this is needed in case an iterator declares IteratorSize to be HasSize
66+ Base. size (tc:: TreeCursor ) = (size ∘ children ∘ nodevalue)(tc)
5867
5968Base. IteratorEltype (:: Type{<:TreeCursor} ) = EltypeUnknown ()
6069
@@ -73,18 +82,21 @@ parent(tc::TreeCursor) = tc.parent
7382
7483
7584"""
76- TrivialCursor{P,N } <: TreeCursor{P,N }
85+ TrivialCursor{N,P } <: TreeCursor{N,P }
7786
7887A [`TreeCursor`](@ref) which matches the functionality of the underlying node. Tree nodes wrapped by this
7988cursor themselves have most of the functionality required of a `TreeCursor`, this type exists entirely
8089for the sake of maintaining a fully consistent interface with other `TreeCursor` objects.
8190"""
82- struct TrivialCursor{P,N } <: TreeCursor{P,N }
83- parent:: P
91+ struct TrivialCursor{N,P } <: TreeCursor{N,P }
92+ parent:: P # unlike in most other cursors, this is not a cursor
8493 node:: N
8594end
8695
87- parent (csr:: TrivialCursor ) = parent (csr. node)
96+ function parent (csr:: TrivialCursor )
97+ isnothing (csr. parent) && return nothing
98+ TrivialCursor (parent (csr. parent), csr. parent)
99+ end
88100
89101TrivialCursor (node) = TrivialCursor (parent (node), node)
90102
@@ -109,34 +121,35 @@ end
109121
110122
111123"""
112- ImplicitCursor{P,N, S} <: TreeCursor{P,N }
124+ ImplicitCursor{N,P, S} <: TreeCursor{N,P }
113125
114126A [`TreeCursor`](@ref) which wraps nodes which cannot efficiently access either their parents or siblings directly.
115127This should be thought of as a "worst case scenario" tree cursor. In particular, `ImplicitCursor`s store the
116128child iteration state of type `S` and for any of `ImplicitCursor`s method to be type-stable it must be possible
117129to infer the child iteration state type, see [`childstatetype`](@ref).
118130"""
119- struct ImplicitCursor{P,N, S} <: TreeCursor{P,N }
120- parent:: P
131+ struct ImplicitCursor{N,P, S} <: TreeCursor{N,P }
132+ parent:: Union{Nothing,ImplicitCursor}
121133 node:: N
122- sibling_state :: S
134+ nextsibstate :: S
123135
124- ImplicitCursor (p:: Union{Nothing,ImplicitCursor} , n, s= InitialState ()) = new {typeof(p),typeof(n),typeof(s)} (p, n, s)
136+ function ImplicitCursor (p:: Union{Nothing,ImplicitCursor} , n, s)
137+ cst = isnothing (p) ? Any : childstatetype (nodevalue (p))
138+ new {typeof(n),typeof(nodevalue(p)),cst} (p, n, s)
139+ end
125140end
126141
127- ImplicitCursor (node) = ImplicitCursor (nothing , node)
142+ ImplicitCursor (node) = ImplicitCursor (nothing , node, nothing )
128143
129- Base. IteratorEltype (:: Type{<:ImplicitCursor} ) = HasEltype ()
144+ Base. IteratorEltype (:: Type{<:ImplicitCursor} ) = EltypeUnknown ()
130145
131- function Base. eltype (:: Type{ImplicitCursor{P,N,S}} ) where {P,N,S}
132- cst = (childstatetype ∘ nodevalueeltype)(P)
133- P′ = ImplicitCursor{P,N,S}
134- ImplicitCursor{P′,childtype (N),cst}
146+ function Base. eltype (:: Type{ImplicitCursor{N,P,S}} ) where {N,P,S}
147+ ImplicitCursor{childtype (N),N,childstatetype (P)}
135148end
136149
137150function Base. eltype (csr:: ImplicitCursor )
138151 cst = (childstatetype ∘ parent ∘ nodevalue)(csr)
139- ImplicitCursor{typeof (csr), childtype (nodevalue (csr)),cst}
152+ ImplicitCursor{childtype (nodevalue (csr)), nodevaluetype (csr ),cst}
140153end
141154
142155function Base. iterate (csr:: ImplicitCursor , s= InitialState ())
@@ -145,23 +158,23 @@ function Base.iterate(csr::ImplicitCursor, s=InitialState())
145158 r = s isa InitialState ? iterate (cs) : iterate (cs, s)
146159 isnothing (r) && return nothing
147160 (n′, s′) = r
148- o = ImplicitCursor (csr, n′, s′)
161+ # next cursor requires 1 extra iteration to store next sibling
162+ ns = iterate (cs, s′)
163+ o = ImplicitCursor (csr, n′, ns)
149164 (o, s′)
150165end
151166
152167function nextsibling (csr:: ImplicitCursor )
153- isroot (csr) && return nothing
154- cs = (children ∘ nodevalue ∘ parent)(csr)
155- # do NOT just write an iterate(x, ::InitialState) method, it's an ambiguity nightmare
156- r = csr. sibling_state isa InitialState ? iterate (cs) : iterate (cs, csr. sibling_state)
157- isnothing (r) && return nothing
158- (n′, s′) = r
159- ImplicitCursor (parent (csr), n′, s′)
168+ st = csr. nextsibstate
169+ isnothing (st) && return nothing
170+ (n, s) = st
171+ ns = iterate (children (nodevalue (parent (csr))), s)
172+ ImplicitCursor (csr. parent, n, ns)
160173end
161174
162175
163176"""
164- IndexedCursor{P,N } <: TreeCursor{P,N }
177+ IndexedCursor{N,P } <: TreeCursor{N,P }
165178
166179A [`TreeCursor`](@ref) for tree nodes with the [`IndexedChildren`](@ref) trait but for which parents and siblings
167180are not directly accessible.
@@ -170,23 +183,20 @@ This type is very similar to [`ImplicitCursor`](@ref) except that it is free to
170183state is an integer starting at `1` which drastially simplifies type inference and slightly simplifies the
171184iteration methods.
172185"""
173- struct IndexedCursor{P,N } <: TreeCursor{P,N }
174- parent:: P
186+ struct IndexedCursor{N,P } <: TreeCursor{N,P }
187+ parent:: Union{Nothing,IndexedCursor}
175188 node:: N
176189 index:: Int
177190
178- IndexedCursor (p:: Union{Nothing,IndexedCursor} , n, idx:: Integer = 1 ) = new {typeof(p ),typeof(n )} (p, n, idx)
191+ IndexedCursor (p:: Union{Nothing,IndexedCursor} , n, idx:: Integer = 1 ) = new {typeof(n ),typeof(nodevalue(p) )} (p, n, idx)
179192end
180193
181- IndexedCursor (node) = IndexedCursor (nothing , node)
194+ IndexedCursor (node) = IndexedCursor (nothing , node)
182195
183196Base. IteratorSize (:: Type{<:IndexedCursor} ) = HasLength ()
184197
185- function Base. eltype (:: Type{IndexedCursor{P,N}} ) where {P,N}
186- P′ = IndexedCursor{P,N}
187- IndexedCursor{P′,childtype (N)}
188- end
189- Base. eltype (csr:: IndexedCursor ) = IndexedCursor{typeof (csr),childtype (nodevalue (csr))}
198+ Base. eltype (:: Type{IndexedCursor{N,P}} ) where {N,P} = IndexedCursor{childtype (N),N}
199+ Base. eltype (csr:: IndexedCursor ) = IndexedCursor{childtype (nodevalue (csr)),nodevaluetype (csr)}
190200Base. length (csr:: IndexedCursor ) = (length ∘ children ∘ nodevalue)(csr)
191201
192202function Base. getindex (csr:: IndexedCursor , idx)
@@ -215,38 +225,30 @@ end
215225
216226
217227"""
218- SiblingCursor{P,N } <: TreeCursor{P,N }
228+ SiblingCursor{N,P } <: TreeCursor{N,P }
219229
220230A [`TreeCursor`](@ref) for trees with the [`StoredSiblings`](@ref) trait.
221231"""
222- struct SiblingCursor{P,N } <: TreeCursor{P,N }
223- parent:: P
232+ struct SiblingCursor{N,P } <: TreeCursor{N,P }
233+ parent:: Union{Nothing,SiblingCursor}
224234 node:: N
225235
226- SiblingCursor (p:: Union{Nothing,SiblingCursor} , n) = new {typeof(p ),typeof(n )} (p, n)
236+ SiblingCursor (p:: Union{Nothing,SiblingCursor} , n) = new {typeof(n ),typeof(nodevalue(p) )} (p, n)
227237end
228238
229239SiblingCursor (node) = SiblingCursor (nothing , node)
230240
231- Base. IteratorSize (:: Type{SiblingCursor{P,N}} ) where {P,N} = IteratorSize (childtype (N))
232-
233241Base. IteratorEltype (:: Type{<:SiblingCursor} ) = HasEltype ()
234242
235- function Base. eltype (:: Type{SiblingCursor{P,N}} ) where {P,N}
236- cst = (childstatetype ∘ nodevaluetype)(P)
237- P′ = SiblingCursor{P,N}
238- SiblingCursor{P′,childtype (N)}
239- end
240-
241- Base. eltype (csr:: SiblingCursor ) = SiblingCursor{typeof (csr),childtype (nodevalue (csr))}
243+ Base. eltype (:: Type{SiblingCursor{N,P}} ) where {N,P} = SiblingCursor{childtype (N),N}
242244
243- function Base. iterate (csr:: SiblingCursor , (c, s) = ( nothing , InitialState () ))
245+ function Base. iterate (csr:: SiblingCursor , s = InitialState ())
244246 cs = (children ∘ nodevalue)(csr)
245247 r = s isa InitialState ? iterate (cs) : iterate (cs, s)
246248 isnothing (r) && return nothing
247249 (n′, s′) = r
248250 o = SiblingCursor (csr, n′)
249- (o, (o, s′) )
251+ (o, s′ )
250252end
251253
252254function nextsibling (csr:: SiblingCursor )
@@ -260,11 +262,98 @@ function prevsibling(csr::SiblingCursor)
260262end
261263
262264
263- TreeCursor (:: ChildIndexing , :: StoredParents , :: StoredSiblings , node) = TrivialCursor (node)
265+ struct StableCursor{N,S} <: TreeCursor{N,N}
266+ parent:: Union{Nothing,StableCursor{N,S}}
267+ node:: N
268+ # includes the full return type of `iterate` for siblings and is guaranteed to be a
269+ # Union{Nothing,T} type
270+ nextsibstate:: S
271+
272+ # note that this very deliberately takes childstatetype(n) and *not* childstatetype(p)
273+ # this is because p may be nothing
274+ StableCursor (p, n, st) = new {typeof(n),childstatetype(n)} (p, n, st)
275+ end
276+
277+ StableCursor (node) = StableCursor (nothing , node, nothing )
278+
279+ Base. IteratorEltype (:: Type{<:StableCursor} ) = HasEltype ()
280+
281+ Base. eltype (:: Type{T} ) where {T<: StableCursor } = T
282+
283+ function Base. iterate (csr:: StableCursor , s= InitialState ())
284+ cs = (children ∘ nodevalue)(csr)
285+ r = s isa InitialState ? iterate (cs) : iterate (cs, s)
286+ isnothing (r) && return nothing
287+ (n′, s′) = r
288+ # next cursor requires 1 extra iteration to store next sibling
289+ ns = iterate (cs, s′)
290+ o = StableCursor (csr, n′, ns)
291+ (o, s′)
292+ end
293+
294+ function nextsibling (csr:: StableCursor )
295+ st = csr. nextsibstate
296+ isnothing (st) && return nothing
297+ # if we got here it also guarantees that there are more siblings
298+ (n, s) = st
299+ ns = iterate (children (nodevalue (parent (csr))), s)
300+ StableCursor (csr. parent, n, ns)
301+ end
302+
303+
304+ struct StableIndexedCursor{N} <: TreeCursor{N,N}
305+ parent:: Union{Nothing,StableIndexedCursor{N}}
306+ node:: N
307+ index:: Int
308+
309+ StableIndexedCursor (p:: Union{Nothing,StableIndexedCursor} , n, idx:: Integer = 1 ) = new {typeof(n)} (p, n, idx)
310+ end
311+
312+ StableIndexedCursor (node) = StableIndexedCursor (nothing , node)
313+
314+ Base. IteratorSize (:: Type{<:StableIndexedCursor} ) = HasLength ()
315+
316+ Base. IteratorEltype (:: Type{<:StableIndexedCursor} ) = HasEltype ()
317+
318+ Base. eltype (:: Type{T} ) where {T<: StableIndexedCursor } = T
319+
320+ Base. length (csr:: StableIndexedCursor ) = (length ∘ children ∘ nodevalue)(csr)
321+
322+ function Base. getindex (csr:: StableIndexedCursor , idx)
323+ cs = (children ∘ nodevalue)(csr)
324+ StableIndexedCursor (csr, cs[idx], idx)
325+ end
326+
327+ function Base. iterate (csr:: StableIndexedCursor , idx= 1 )
328+ idx > length (csr) && return nothing
329+ (csr[idx], idx+ 1 )
330+ end
331+
332+ function nextsibling (csr:: StableIndexedCursor )
333+ p = parent (csr)
334+ isnothing (p) && return nothing
335+ idx = csr. index + 1
336+ idx > length (p) && return nothing
337+ p[idx]
338+ end
339+
340+ function prevsibling (csr:: StableIndexedCursor )
341+ idx = csr. index - 1
342+ idx < 1 && return nothing
343+ parent (csr)[idx]
344+ end
345+
346+
347+ TreeCursor (node) = TreeCursor (NodeType (node), ChildIndexing (node), ParentLinks (node), SiblingLinks (node), node)
348+
349+ TreeCursor (:: HasNodeType , :: IndexedChildren , :: ParentLinks , :: SiblingLinks , node) = StableIndexedCursor (node)
350+ TreeCursor (:: HasNodeType , :: NonIndexedChildren , :: ParentLinks , :: SiblingLinks , node) = StableCursor (node)
351+
352+ TreeCursor (:: NodeTypeUnknown , :: IndexedChildren , :: ParentLinks , :: SiblingLinks , node) = IndexedCursor (node)
353+
354+ TreeCursor (:: NodeTypeUnknown , :: ChildIndexing , :: StoredParents , :: StoredSiblings , node) = TrivialCursor (node)
264355
265- TreeCursor (:: ChildIndexing , :: ImplicitParents , :: StoredSiblings , node) = SiblingCursor (node)
356+ TreeCursor (:: NodeTypeUnknown , :: ChildIndexing , :: ImplicitParents , :: StoredSiblings , node) = SiblingCursor (node)
266357
267- TreeCursor (:: NonIndexedChildren , :: ParentLinks , :: ImplicitSiblings , node) = ImplicitCursor (node)
268- TreeCursor (:: IndexedChildren , :: ParentLinks , :: ImplicitSiblings , node) = IndexedCursor (node)
358+ TreeCursor (:: NodeTypeUnknown , :: NonIndexedChildren , :: ParentLinks , :: ImplicitSiblings , node) = ImplicitCursor (node)
269359
270- TreeCursor (node) = TreeCursor (ChildIndexing (node), ParentLinks (node), SiblingLinks (node), node)
0 commit comments