[Haskell-beginners] Traverse tree with computing current level using Foldable instance.
Dmitriy Matrosov
sgf.dma at gmail.com
Thu May 24 13:09:24 CEST 2012
On 05/23/12 20:48, Chaddaï Fouché wrote:
> The solution now looks like that :
>
>> foldTapeD :: (Monoid m) => (Int -> a -> m) -> Tape a -> m
>> foldTapeD f t = (foldTape go t) 0
>> where
>> go x fs n = ....
>
> I let you write your solution (if you didn't find before tomorrow
> evening, I'll give you the answer).
>
> You can then call foldTapeD thus :
>> foldTapeD (\n x -> if n< 2 then [x] else []) testTape
>
> (much nicer than your initial solution, is it not ?)
Hi, Chaddaï. Thanks for the clarification!
Now i think i get it. Here is three my solutions. First one is (as you
suggest)
without monads:
> import Data.Monoid
> import Control.Monad.State
>
> data Tape a = Tape a [Tape a]
>
> foldTape :: (a -> [b] -> b) -> Tape a -> b
> foldTape f (Tape name ts)
> = f name (map (foldTape f) ts)
>
> foldTapeD :: (Monoid m) => (Int -> a -> m) -> Tape a -> m
> foldTapeD f t = (foldTape (go f) t) 0
> where
> go :: (Monoid m) => (Int -> a -> m) -> a -> [(Int -> m)] -> (Int
-> m)
> go f name xs = \cs ->
> foldr (mappend . ($ (cs + 1))) (f cs name) xs
second one with monadic go function:
> foldTapeD1 :: (Monoid m) => (Int -> a -> m) -> Tape a -> m
> foldTapeD1 f t = fst $ runState (foldTape (go f) t) 0
> where
> go :: (Monoid m) => (Int -> a -> m) -> a -> [State Int m] ->
State Int m
> go f name xs = do
> cs <- get
> put (cs + 1)
> foldr (go' (cs + 1)) (return (f cs name)) xs
> go' :: (Monoid m) => Int -> State Int m -> State Int m -> State Int m
> go' cs mx mz = do
> x <- mx
> put cs
> z <- mz
> put cs
> return (x `mappend` z)
and the last one with monadic go function and monadic user-defined folding
function:
> foldTapeD2 :: (Monoid m) => (a -> State Int m) -> Tape a -> m
> foldTapeD2 f t = fst $ runState (foldTape (go f) t) 0
> where
> go :: (Monoid m) =>
> (a -> State Int m) -> a -> [State Int m] -> State Int m
> go f name xs = do
> cs <- get
> z <- f name
> put (cs + 1)
> foldr (go' (cs + 1)) (return z) xs
> go' :: (Monoid m) => Int -> State Int m -> State Int m -> State Int m
> go' cs mx mz = do
> x <- mx
> put cs
> z <- mz
> put cs
> return (x `mappend` z)
and here is test functions:
> testTape :: Tape String
> testTape = Tape "A" [ Tape "B" [ Tape "C" []
> , Tape "F" [Tape "G"
> [Tape
"H" []]]
> , Tape "E" []
> ]
> , Tape "D" [ Tape "I" []]
> ]
> testFoldTapeD :: ((Int -> a -> [a]) -> Tape a -> [a]) ->
> Int -> Tape a -> [a]
> testFoldTapeD ftD i t = ftD (\cs x -> if cs == i then [x] else []) t
> testFoldTapeD1 :: ((a -> State Int [a]) -> Tape a -> [a]) ->
> Int -> Tape a -> [a]
> testFoldTapeD1 ftD i t
> = ftD (\x -> get >>= \cs -> if cs == i then return [x] else
return []) t
Is my answer correct? :)
And at the end it seems, that first (non-monadic) version is much
simpler and
clearer, than all other. So.. should i use monads here?
Earlier i think, that it's better to use them, but now i doubt.
--
Dmitriy Matrosov
More information about the Beginners
mailing list