
apfelmus wrote:
Andreas-Christoph Bernstein wrote:
Is there a pattern for tree traversal with a state ?
I am developing a small scenegraph represented by a tree. To draw a scenegraph one traverses over the graph starting with a global state. Inner Nodes can overwrite the inherited state for their subtree (e.g. Transformations are accumulated). The accumulated state is then either used immediately to draw the geometry in the leaf nodes, or a secondary data structure is build. This secondary data structure (a list or a tree) can then be sorted for optimal drawing performance.
So i want to do the second and create a list of all leaves with the accumulated global state. To illustrate my problem i appended some code. The idea similar applies to a scenegraph.
So my Question is: Is there already a pattern for traversal with a state ?
Yes. I'm not sure whether state is really necessary for your problem, i.e. whether there is a more elegant formulation, but your algorithm fits a well-known pattern, namely the one in Data.Traversable
import Data.Traversable import Data.Foldable
import qualified Control.Monad.State
data BTree a = Fork a (BTree a) (BTree a) | Leaf a deriving Show
-- main functionality instance Traversable BTree where traverse f (Leaf x) = Leaf <$> f x traverse f (Fork x l r) = Fork <$> f x <*> traverse f l <*> traverse f r
-- derived examples instance Foldable BTree where foldMap = foldMapDefault instance Functor BTree where fmap = fmapDefault
flattenTree = toList
-- state example data StateMod = ModInt | ModString | ModNop deriving Show type State = (Int, String)
modState :: StateMod -> State -> State modState ModInt (x,w) = (x+1,w) modState ModNop s = s modState ModString (x,w) = (x,'b':w)
startState = (0,"a")
newTree :: BTree StateMod -> BTree State newTree = flip evalState startState . Data.Traversable.mapM (modify' . modState) where modify' f = Control.Monad.State.modify f >> Control.Monad.State.get
Hi, Thanks for the quick reply. But it is not quite what i expect. If i apply your solution to an exampletree i get the following result: tree :: BTree StateMod tree = Fork ModNop (Fork ModInt (Leaf ModInt) (Leaf ModNop)) (Leaf ModNop) flattenTree (newTree tree ) which produces: [(0,"a"),(1,"a"),(2,"a"),(2,"a"),(2,"a")] But what i need is [(0,"a"),(1,"a"),(2,"a"),(1,"a"),(0,"a")] So state changes should affect only their subtree, not the rest of the tree to the right. Kind regards, Andreas