pattern for tree traversel with a state
 
            Hi, 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 allready a pattern for traversal with a state ?
module Main where
produces: Fork (0,"a") (Fork (1,"a") (Leaf (2,"a")) (Leaf (1,"a"))) (Leaf (0,"a"))
newTree :: BTree State newTree = traverse modState globalState sampleTree
produces: [(0,"a"),(1,"a"),(2,"a"),(1,"a"),(0,"a")]
stateList = flattenTree newTree
flattenTree (Leaf x) = [x] flattenTree (Fork x l r) = [x] ++ flattenTree l ++ flattenTree r
type State = (Int, String)
globalState :: State globalState = (0, "a")
State modifiers
data StateMod = ModInt | ModString | ModNop deriving Show
modState :: StateMod -> State -> State modState ModInt (x,w) = (x+1,w) modState ModNop s = s modState ModString (x,w) = (x,'b':w)
data BTree a = Fork a (BTree a) (BTree a) | Leaf a deriving Show
traverses the tree and executes a function which modifies the current state depending on the statemodifier
traverse :: (a -> b -> b) -> b -> BTree a -> BTree b traverse f state (Leaf x) = Leaf (f x state) traverse f state (Fork x l r) = Fork (f x state) newLeft newRight where newLeft = traverse f (f x state) l newRight = traverse f (f x state) r
an example tree
sampleTree :: BTree StateMod sampleTree = Fork ModNop (Fork ModInt (Leaf ModInt) (Leaf ModNop)) (Leaf ModNop)
creates a list from a tree
flattenTree (Leaf x) = [x] flattenTree (Fork x l r) = [x] ++ flattenTree l ++ flattenTree r
Thanks for any help and ideas Andreas
 
            Andreas-Christoph, I'm afraid I can't help answering your question, but I was wondering what you were using to create your scene graph? I'm currently having to use OpenSceneGraph in C++, and would be grateful if you knew of some kind of Haskell wrapper for this? Kind regards, Chris. On Thu, 23 Oct 2008, Andreas-Christoph Bernstein wrote:
Hi,
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 allready a pattern for traversal with a state ?
module Main where
produces: Fork (0,"a") (Fork (1,"a") (Leaf (2,"a")) (Leaf (1,"a"))) (Leaf (0,"a"))
newTree :: BTree State newTree = traverse modState globalState sampleTree
produces: [(0,"a"),(1,"a"),(2,"a"),(1,"a"),(0,"a")]
stateList = flattenTree newTree
flattenTree (Leaf x) = [x] flattenTree (Fork x l r) = [x] ++ flattenTree l ++ flattenTree r
type State = (Int, String)
globalState :: State globalState = (0, "a")
State modifiers
data StateMod = ModInt | ModString | ModNop deriving Show
modState :: StateMod -> State -> State modState ModInt (x,w) = (x+1,w) modState ModNop s = s modState ModString (x,w) = (x,'b':w)
data BTree a = Fork a (BTree a) (BTree a) | Leaf a deriving Show
traverses the tree and executes a function which modifies the current state depending on the statemodifier
traverse :: (a -> b -> b) -> b -> BTree a -> BTree b traverse f state (Leaf x) = Leaf (f x state) traverse f state (Fork x l r) = Fork (f x state) newLeft newRight where newLeft = traverse f (f x state) l newRight = traverse f (f x state) r
an example tree
sampleTree :: BTree StateMod sampleTree = Fork ModNop (Fork ModInt (Leaf ModInt) (Leaf ModNop)) (Leaf ModNop)
creates a list from a tree
flattenTree (Leaf x) = [x] flattenTree (Fork x l r) = [x] ++ flattenTree l ++ flattenTree r
Thanks for any help and ideas
Andreas _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
 
            hi, well i dont know about any haskell wrapper for openscenegraph. There are some python wrappers. (pyosg, avango). What i want to do is to use haskell for some simple graphics hacking, demo effects and to test ideas. Kind regards, Andreas C.M.Brown wrote:
Andreas-Christoph,
I'm afraid I can't help answering your question, but I was wondering what you were using to create your scene graph? I'm currently having to use OpenSceneGraph in C++, and would be grateful if you knew of some kind of Haskell wrapper for this?
Kind regards, Chris.
On Thu, 23 Oct 2008, Andreas-Christoph Bernstein wrote:
Hi,
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 allready a pattern for traversal with a state ?
module Main where
produces: Fork (0,"a") (Fork (1,"a") (Leaf (2,"a")) (Leaf (1,"a"))) (Leaf (0,"a"))
newTree :: BTree State newTree = traverse modState globalState sampleTree
produces: [(0,"a"),(1,"a"),(2,"a"),(1,"a"),(0,"a")]
stateList = flattenTree newTree
flattenTree (Leaf x) = [x] flattenTree (Fork x l r) = [x] ++ flattenTree l ++ flattenTree r
type State = (Int, String)
globalState :: State globalState = (0, "a")
State modifiers
data StateMod = ModInt | ModString | ModNop deriving Show
modState :: StateMod -> State -> State modState ModInt (x,w) = (x+1,w) modState ModNop s = s modState ModString (x,w) = (x,'b':w)
data BTree a = Fork a (BTree a) (BTree a) | Leaf a deriving Show
traverses the tree and executes a function which modifies the current state depending on the statemodifier
traverse :: (a -> b -> b) -> b -> BTree a -> BTree b traverse f state (Leaf x) = Leaf (f x state) traverse f state (Fork x l r) = Fork (f x state) newLeft newRight where newLeft = traverse f (f x state) l newRight = traverse f (f x state) r
an example tree
sampleTree :: BTree StateMod sampleTree = Fork ModNop (Fork ModInt (Leaf ModInt) (Leaf ModNop)) (Leaf ModNop)
creates a list from a tree
flattenTree (Leaf x) = [x] flattenTree (Fork x l r) = [x] ++ flattenTree l ++ flattenTree r
Thanks for any help and ideas
Andreas _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
 
            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 Regards, apfelmus
 
            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
 
            2008/10/23 Andreas-Christoph Bernstein 
apfelmus wrote:
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.
It seems to me that you are looking for the Reader monad. Try the following: import Control.Monad.Reader t :: (a -> b -> b) -> BTree a -> Reader b (BTree b) t f (Leaf x) = do s <- ask return (Leaf (f x s)) t f (Fork x l r) = do s <- ask l' <- local (f x) (t f l) r' <- local (f x) (t f r) return (Fork (f x s) l' r') new = runReader (t modState sampleTree) globalState Then, flattenTree new gives you [(0,"a"),(1,"a"),(2,"a"),(1,"a"),(0,"a")] I think that the Reader monad is a standard way to this. When you want the state to affect also the rest of the tree then use the State monad. Sincerely, jan.
 
            On Thu, Oct 23, 2008 at 11:47:43PM +0100, Jan Jakubuv wrote:
2008/10/23 Andreas-Christoph Bernstein
: apfelmus wrote:
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.
It seems to me that you are looking for the Reader monad. Try the following:
import Control.Monad.Reader
t :: (a -> b -> b) -> BTree a -> Reader b (BTree b) t f (Leaf x) = do s <- ask return (Leaf (f x s)) t f (Fork x l r) = do s <- ask l' <- local (f x) (t f l) r' <- local (f x) (t f r) return (Fork (f x s) l' r')
new = runReader (t modState sampleTree) globalState
Then,
flattenTree new
gives you
[(0,"a"),(1,"a"),(2,"a"),(1,"a"),(0,"a")]
I think that the Reader monad is a standard way to this. When you want the state to affect also the rest of the tree then use the State monad.
Just to elaborate on Jan's code, the Reader monad represents an *immutable* state---that is, a read-only "environment" that gets threaded through your computation which you can access at any time (using "ask"). However, using the "local" function, you can run subcomputations within a different environment, obtained by applying some function to the current environment. So this does exactly what you want---after the subcomputation is finished, its locally defined environment goes out of scope and you are back to the original environment. Using the Reader monad in this way is a common idiom for representing recursive algorithms with state that can change on the way down the call stack, but "unwinds" as you come back up, so recursive calls can only affect recursive calls below them, not ones that come afterwards. -Brent
 
            Brent Yorgey wrote:
On Thu, Oct 23, 2008 at 11:47:43PM +0100, Jan Jakubuv wrote:
2008/10/23 Andreas-Christoph Bernstein
: apfelmus wrote:
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.
It seems to me that you are looking for the Reader monad. Try the following:
import Control.Monad.Reader
t :: (a -> b -> b) -> BTree a -> Reader b (BTree b) t f (Leaf x) = do s <- ask return (Leaf (f x s)) t f (Fork x l r) = do s <- ask l' <- local (f x) (t f l) r' <- local (f x) (t f r) return (Fork (f x s) l' r')
new = runReader (t modState sampleTree) globalState
Then,
flattenTree new
gives you
[(0,"a"),(1,"a"),(2,"a"),(1,"a"),(0,"a")]
I think that the Reader monad is a standard way to this. When you want the state to affect also the rest of the tree then use the State monad.
Just to elaborate on Jan's code, the Reader monad represents an *immutable* state---that is, a read-only "environment" that gets threaded through your computation which you can access at any time (using "ask"). However, using the "local" function, you can run subcomputations within a different environment, obtained by applying some function to the current environment. So this does exactly what you want---after the subcomputation is finished, its locally defined environment goes out of scope and you are back to the original environment. Using the Reader monad in this way is a common idiom for representing recursive algorithms with state that can change on the way down the call stack, but "unwinds" as you come back up, so recursive calls can only affect recursive calls below them, not ones that come afterwards.
-Brent
That is what i was looking for. Thank you all very much for your help. Kind regards, Andreas
participants (5)
- 
                 Andreas-Christoph Bernstein Andreas-Christoph Bernstein
- 
                 apfelmus apfelmus
- 
                 Brent Yorgey Brent Yorgey
- 
                 C.M.Brown C.M.Brown
- 
                 Jan Jakubuv Jan Jakubuv