[Haskell-beginners] Traverse tree with computing current level using Foldable instance.

Dmitriy Matrosov sgf.dma at gmail.com
Mon May 21 12:28:03 CEST 2012


Hi.

I can't figure out how should i properly solve the following problem.
There is a tree defined like

data Tape a             =  Tape a [Tape a]

and i want to traverse it in some specific order, computing at the same 
time current level (depth). I.e. it should like fold, and folding 
function should have access to current level in the tree. Here is my 
implementation:

import Data.Monoid
import Control.Monad.State

type TapeState a        =  State Int a
foldMapS2               :: (Monoid m) => (a -> TapeState m) -> TapeState 
(Tape a) -> TapeState m
foldMapS2 f tt          =  do
     t@(Tape name ts) <- tt
     foldr (go f) (f name) ts
   where
     go                  :: (Monoid m) => (a -> TapeState m) -> Tape a 
-> TapeState m -> TapeState m
     go f t mz           =  do
         cs <- get
         x <- foldMapS2 f (State (\s -> (t, s + 1)))
         put cs
         z <- mz
         put cs
         return (x `mappend` z)

and here is example usage

testTape                =  Tape "A" [ Tape "B"  [ Tape "C" []
                                                 , Tape "F" [Tape "G" 
[Tape "H" []]]
                                                 , Tape "E" []
                                                 ]
                                     , Tape "D"  [ Tape "I" []]
                                     ]

*Main> runState (foldMapS2 (\name -> get >>= \cs -> if cs == 0 then 
return [name] else return mempty) (return (testTape))) 0
(["A"],0)
*Main> runState (foldMapS2 (\name -> get >>= \cs -> if cs == 1 then 
return [name] else return mempty) (return (testTape))) 0
(["B","D"],0)
*Main> runState (foldMapS2 (\name -> get >>= \cs -> if cs == 2 then 
return [name] else return mempty) (return (testTape))) 0
(["C","F","E","I"],0)
*Main> runState (foldMapS2 (\name -> get >>= \cs -> if cs == 3 then 
return [name] else return mempty) (return (testTape))) 0
(["G"],0)
*Main> runState (foldMapS2 (\name -> get >>= \cs -> if cs == 4 then 
return [name] else return mempty) (return (testTape))) 0
(["H"],0)
*Main> runState (foldMapS2 (\name -> get >>= \cs -> if cs == 5 then 
return [name] else return mempty) (return (testTape))) 0
([],0)

As you can see, this just selects all elements at particular tree level.

So, my foldMapS2 looks similar to foldMap from Foldable, but i can't 
figure out, how should i define instances of Foldable (and Monoid?) to 
achieve the same functionality?



More information about the Beginners mailing list