
So I am trying to traverse a tree in a specific order, but i have no idea where the things that i am looking for are located, and i want to avoid explicit backtracking. I was thinking i could do it with the continuation monad. Here is what i have module TestCont where import Control.Monad.Cont import Control.Monad.Identity import Control.Monad.State.Lazy --our stupid tree data Tree a = Tree [Tree a] | Leaf a --traverse all the branches search (Tree ts) next = do mapM_ (\ ti -> (callCC (search ti))) ts next $ () search tt@(Leaf a) next = do cur <- lift get case ((cur + 1) == a) of True -> do --the current leaf is what we want, update the state and return lift $ put a return $ () False -> do --the current leaf is not what we want, continue first, then try again next () search tt (\ _ -> error "fail") t1 = Leaf 1 t2 = Leaf 2 t3 = Tree [t1,t2] t4 = Leaf 3 t5::Tree Int = Tree [t4,t3] run = runIdentity (runStateT ((runContT $ callCC (search t5)) return) 0) it seems like next isn't quite doing what i want, because i don't think I ever try again after i call next $ () in the second clause. Any ideas? Thanks, Anatoly

On Fri, May 1, 2009 at 8:47 PM, Anatoly Yakovenko
So I am trying to traverse a tree in a specific order, but i have no idea where the things that i am looking for are located, and i want to avoid explicit backtracking.
Though I don't fully understand what you are doing (specifically what you mean by "specific order"), but in a lazy language, traversals are usually simply encoded as lists. Just write a function which returns all the leaves as a list, and filter over it. traverse (Tree ts) = concatMap traverse ts traverse (Leaf x) = [x] I believe this simple definition has more overhead than necessary because of all the appends; a DList will be more efficient. import qualified Data.DList as DList traverse = DList.toList . traverse' where traverse' t (Tree ts) = DList.concat (map traverse' ts) traverse' t (Leaf x) = DList.singleton x (DList is on hackage) I was thinking i could do it with the
continuation monad. Here is what i have
module TestCont where import Control.Monad.Cont import Control.Monad.Identity import Control.Monad.State.Lazy
--our stupid tree data Tree a = Tree [Tree a] | Leaf a
--traverse all the branches search (Tree ts) next = do mapM_ (\ ti -> (callCC (search ti))) ts next $ ()
search tt@(Leaf a) next = do cur <- lift get case ((cur + 1) == a) of True -> do --the current leaf is what we want, update the state and return lift $ put a return $ () False -> do --the current leaf is not what we want, continue first, then try again next () search tt (\ _ -> error "fail")
t1 = Leaf 1 t2 = Leaf 2 t3 = Tree [t1,t2] t4 = Leaf 3 t5::Tree Int = Tree [t4,t3]
run = runIdentity (runStateT ((runContT $ callCC (search t5)) return) 0)
it seems like next isn't quite doing what i want, because i don't think I ever try again after i call next $ () in the second clause. Any ideas?
Thanks, Anatoly _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Though I don't fully understand what you are doing (specifically what you mean by "specific order"), but in a lazy language, traversals are usually simply encoded as lists. Just write a function which returns all the leaves as a list, and filter over it.
yea, i know, i am trying to learn how to use the Cont monad. or continuation in haskell. The idea is that while i am processing some data i may hit a point whree some dependency isn't met and i want to take a different branch via continuation. I expect that branch to furfill my dependency and when its done i want to continue down the original branch
module TestCont where import Control.Monad.Cont import Control.Monad.Identity import Control.Monad.State.Lazy
--our stupid tree data Tree a = Tree [Tree a] | Leaf a
--traverse all the branches search (Tree ts) next = do mapM_ (\ ti -> (callCC (search ti))) ts next $ ()
search tt@(Leaf a) next = do cur <- lift get case ((cur + 1) == a) of True -> do --the current leaf is what we want, update the state and return
this is where i succeed in my current branch, so i can just do my thing and exit
lift $ put a return $ () False -> do --the current leaf is not what we want, continue first, then try again
this is where i fail, so i want to take the "other" branch first expecting it to fulfill my dependency.
next () search tt (\ _ -> error "fail")
t1 = Leaf 1 t2 = Leaf 2 t3 = Tree [t1,t2] t4 = Leaf 3 t5::Tree Int = Tree [t4,t3]
run = runIdentity (runStateT ((runContT $ callCC (search t5)) return) 0)
but i think next doesn't do exactly what i think it does

On Sat, May 2, 2009 at 3:13 AM, Anatoly Yakovenkowrote: > > Though I don't fully understand what you are doing (specifically what you > > mean by "specific order"), but in a lazy language, traversals are usually > > simply encoded as lists. Just write a function which returns all the > leaves > > as a list, and filter over it. > > yea, i know, i am trying to learn how to use the Cont monad. or > continuation in haskell. The idea is that while i am processing some > data i may hit a point whree some dependency isn't met and i want to > take a different branch via continuation. I expect that branch to > furfill my dependency and when its done i want to continue down the > original branch Ah I see. Well, in my opinion, Cont is almost never the right answer. Others, who have an easier time thinking about continuations, may differ. In any case, you are stating your problem very imperatively, which may be why you feel inclined to use continuations. E.g. "when it's done I want to continue down the original branch" is talking about control flow. Maybe you really just want to do a topological sort of some data in your tree? How is the tree structure related to the dependencies? How is the tree structure related to your traversal? E.g. are you using a combining function on each branch to a value over its subtrees? Basically I think "do a traversal" is not enough information to answer your question. What is the relationship of the contents of the tree to the *contents *of the traversal? Luke > > > >> module TestCont where > >> import Control.Monad.Cont > >> import Control.Monad.Identity > >> import Control.Monad.State.Lazy > >> > >> --our stupid tree > >> data Tree a = Tree [Tree a] > >> | Leaf a > >> > >> --traverse all the branches > >> search (Tree ts) next = do > >> mapM_ (\ ti -> (callCC (search ti))) ts > >> next $ () > >> > >> search tt@(Leaf a) next = do > >> cur <- lift get > >> case ((cur + 1) == a) of > >> True -> do --the current leaf is what we want, update the state and > return > > this is where i succeed in my current branch, so i can just do my thing and > exit > > >> lift $ put a > >> return $ () > >> False -> do --the current leaf is not what we want, continue first, > then try again > > this is where i fail, so i want to take the "other" branch first > expecting it to fulfill my dependency. > > >> next () > >> search tt (\ _ -> error "fail") > >> > >> t1 = Leaf 1 > >> t2 = Leaf 2 > >> t3 = Tree [t1,t2] > >> t4 = Leaf 3 > >> t5::Tree Int = Tree [t4,t3] > >> > >> run = runIdentity (runStateT ((runContT $ callCC (search t5)) return) > 0) > > > but i think next doesn't do exactly what i think it does >

its a syntax tree, and at some point i hit a type reference who'se declaration will be satisfied in some other part of the tree. the type references are always leaves, so when i hit a typeref, i just want to continue along the rest of the parser until i hit a declaration. My current solution is to do multiple passes, store the declarations in a map in one pass then resolve all the type references in another, but that's kind of boring.

Cont with success and failure isn't Cont; it's something else (albeit similar)
There's a great exposition of using something much like Cont to get
success and failure "for free" here:
http://www-ps.informatik.uni-kiel.de/~sebf/haskell/barefaced-pilferage-of-mo...
-- ryan
On Sat, May 2, 2009 at 2:13 AM, Anatoly Yakovenko
Though I don't fully understand what you are doing (specifically what you mean by "specific order"), but in a lazy language, traversals are usually simply encoded as lists. Just write a function which returns all the leaves as a list, and filter over it.
yea, i know, i am trying to learn how to use the Cont monad. or continuation in haskell. The idea is that while i am processing some data i may hit a point whree some dependency isn't met and i want to take a different branch via continuation. I expect that branch to furfill my dependency and when its done i want to continue down the original branch
module TestCont where import Control.Monad.Cont import Control.Monad.Identity import Control.Monad.State.Lazy
--our stupid tree data Tree a = Tree [Tree a] | Leaf a
--traverse all the branches search (Tree ts) next = do mapM_ (\ ti -> (callCC (search ti))) ts next $ ()
search tt@(Leaf a) next = do cur <- lift get case ((cur + 1) == a) of True -> do --the current leaf is what we want, update the state and return
this is where i succeed in my current branch, so i can just do my thing and exit
lift $ put a return $ () False -> do --the current leaf is not what we want, continue first, then try again
this is where i fail, so i want to take the "other" branch first expecting it to fulfill my dependency.
next () search tt (\ _ -> error "fail")
t1 = Leaf 1 t2 = Leaf 2 t3 = Tree [t1,t2] t4 = Leaf 3 t5::Tree Int = Tree [t4,t3]
run = runIdentity (runStateT ((runContT $ callCC (search t5)) return) 0)
but i think next doesn't do exactly what i think it does _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

thanks, that looks promising, but will probably take me a week to understand :)
On Sun, May 3, 2009 at 2:40 PM, Ryan Ingram
Cont with success and failure isn't Cont; it's something else (albeit similar)
There's a great exposition of using something much like Cont to get success and failure "for free" here: http://www-ps.informatik.uni-kiel.de/~sebf/haskell/barefaced-pilferage-of-mo...
-- ryan
On Sat, May 2, 2009 at 2:13 AM, Anatoly Yakovenko
wrote: Though I don't fully understand what you are doing (specifically what you mean by "specific order"), but in a lazy language, traversals are usually simply encoded as lists. Just write a function which returns all the leaves as a list, and filter over it.
yea, i know, i am trying to learn how to use the Cont monad. or continuation in haskell. The idea is that while i am processing some data i may hit a point whree some dependency isn't met and i want to take a different branch via continuation. I expect that branch to furfill my dependency and when its done i want to continue down the original branch
module TestCont where import Control.Monad.Cont import Control.Monad.Identity import Control.Monad.State.Lazy
--our stupid tree data Tree a = Tree [Tree a] | Leaf a
--traverse all the branches search (Tree ts) next = do mapM_ (\ ti -> (callCC (search ti))) ts next $ ()
search tt@(Leaf a) next = do cur <- lift get case ((cur + 1) == a) of True -> do --the current leaf is what we want, update the state and return
this is where i succeed in my current branch, so i can just do my thing and exit
lift $ put a return $ () False -> do --the current leaf is not what we want, continue first, then try again
this is where i fail, so i want to take the "other" branch first expecting it to fulfill my dependency.
next () search tt (\ _ -> error "fail")
t1 = Leaf 1 t2 = Leaf 2 t3 = Tree [t1,t2] t4 = Leaf 3 t5::Tree Int = Tree [t4,t3]
run = runIdentity (runStateT ((runContT $ callCC (search t5)) return) 0)
but i think next doesn't do exactly what i think it does _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, May 3, 2009 at 2:40 PM, Ryan Ingram
wrote: There's a great exposition of using something much like Cont to get success and failure "for free" here: http://www-ps.informatik.uni-kiel.de/~sebf/haskell/barefaced-pilferage-of-mo...
On May 4, 2009, at 10:32 PM, Anatoly Yakovenko wrote:
thanks, that looks promising, but will probably take me a week to understand :)
maybe the article version is easier to grasp: http://www-ps.informatik.uni-kiel.de/~sebf/data/pub/atps09.pdf -Sebastian
participants (4)
-
Anatoly Yakovenko
-
Luke Palmer
-
Ryan Ingram
-
Sebastian Fischer