On Fri, May 1, 2009 at 8:47 PM, Anatoly Yakovenko <aeyakovenko@gmail.com> wrote:
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