
Hello, does somewhere exist function with type like this - manyToOne :: [Iteratee a m b] -> Iteratee a m [b] ? I.e. I need to process one input through many Iteratees indepentently in constant space and collect results. It is similar by type with sequenceM but as far as I understand sequenceM won't use the same input for all Iteratees. Dima

On Thu, Apr 28, 2011 at 11:39 AM, Dmitry Olshansky
Hello,
does somewhere exist function with type like this - manyToOne :: [Iteratee a m b] -> Iteratee a m [b] ?
I.e. I need to process one input through many Iteratees indepentently in constant space and collect results.
It is similar by type with sequenceM but as far as I understand sequenceM won't use the same input for all Iteratees.
I foresee one problem: what is the leftover of 'manyToOne xs' if each x in xs needs different lengths of input? One possible untested-but-compiling solution: import Control.Monad (liftM) import qualified Data.Enumerator as E manyToOne :: Monad m => [E.Iteratee a m b] -> E.Iteratee a m [b] manyToOne [] = return [] manyToOne xs = E.Iteratee $ mapM E.runIteratee xs >>= go where go (E.Yield b s : xs) = liftM (put b s) (go xs) go (E.Error exc : _) = return $ E.Error exc go (E.Continue f : xs) = return $ E.Continue $ go' (E.Continue f : xs) go [] = return $ E.Yield [] (error "manyToOne: never here") go' xs stream = manyToOne $ map apply xs where apply (E.Continue f) = f stream apply step = E.returnI step put b s (E.Yield bs _) = E.Yield (b : bs) s put b s (E.Error exc) = E.Error exc put b s (E.Continue f) = E.Continue (liftM (b:) . f) -- When 'go xs' is a E.Continue, then we just put 'b' on -- the list and let the next round of iteratees decide -- what the leftover will be. HTH, -- Felipe.

On Thu, Apr 28, 2011 at 12:09 PM, Felipe Almeida Lessa
I foresee one problem: what is the leftover of 'manyToOne xs' if each x in xs needs different lengths of input?
One possible untested-but-compiling solution: [snip]
Like I said, that manyToOne implementation isn't very predictable about leftovers. But I guess that if all your iteratees consume the same input OR if you don't care about leftovers, then it should be okay. *Main> E.run $ E.enumList 1 [5 :: Int, 6, 7] E.$$ manyToOne [return 1, maybe 2 id `fmap` E.head, return 3, maybe 4 id `fmap` (E.head >> E.head)] >>= \xs -> (,) xs `fmap` E.head Right ([1,5,3,6],Just 7) *Main> E.run $ E.enumList 10 [5 :: Int, 6, 7] E.$$ manyToOne [return 1, maybe 2 id `fmap` E.head, return 3, maybe 4 id `fmap` (E.head >> E.head)] >>= \xs -> (,) xs `fmap` E.head Right ([1,5,3,6],Just 6) Cheers, -- Felipe.

On Thu, Apr 28, 2011 at 1:10 PM, Felipe Almeida Lessa
On Thu, Apr 28, 2011 at 12:09 PM, Felipe Almeida Lessa
wrote: I foresee one problem: what is the leftover of 'manyToOne xs' if each x in xs needs different lengths of input?
One possible untested-but-compiling solution: [snip]
Like I said, that manyToOne implementation isn't very predictable about leftovers. But I guess that if all your iteratees consume the same input OR if you don't care about leftovers, then it should be okay.
Sorry for replying to myself again. =) I think you can actually give predictable semantics to manyToOne: namely, the leftovers from the last iteratee are returned. This new implementation should be better: import Data.Monoid (mappend) import qualified Data.Enumerator as E manyToOne :: Monad m => [E.Iteratee a m b] -> E.Iteratee a m [b] manyToOne is = E.Iteratee $ mapM E.runIteratee is >>= E.runIteratee . go where go [step] = fmap (:[]) (E.returnI step) go (E.Yield b _ : xs) = fmap (b:) (go xs) go (E.Error exc : _) = E.returnI (E.Error exc) go (E.Continue f : xs) = E.continue $ go' (E.Continue f : xs) go [] = return [] go' xs stream = manyToOne $ feed xs where feed [E.Yield b s] = [E.yield b (s `mappend` stream)] feed (E.Continue f : ys) = f stream : feed ys feed (step : ys) = E.returnI step : feed ys feed [] = [] With the same test as before: *Main> E.run $ E.enumList 1 [5 :: Int, 6, 7] E.$$ manyToOne [return 1, maybe 2 id `fmap` E.head, return 3, maybe 4 id `fmap` (E.head >> E.head)] >>= \xs -> (,) xs `fmap` E.head Right ([1,5,3,6],Just 7) *Main> E.run $ E.enumList 10 [5 :: Int, 6, 7] E.$$ manyToOne [return 1, maybe 2 id `fmap` E.head, return 3, maybe 4 id `fmap` (E.head >> E.head)] >>= \xs -> (,) xs `fmap` E.head Right ([1,5,3,6],Just 7) When the last iteratee doesn't consume anything: *Main> E.run $ E.enumList 1 [5 :: Int, 6, 7] E.$$ manyToOne [return 1, maybe 2 id `fmap` E.head, return 3, maybe 4 id `fmap` (E.head >> E.head), return 10] >>= \xs -> (,) xs `fmap` E.head Right ([1,5,3,6,10],Just 5) *Main> E.run $ E.enumList 10 [5 :: Int, 6, 7] E.$$ manyToOne [return 1, maybe 2 id `fmap` E.head, return 3, maybe 4 id `fmap` (E.head >> E.head), return 10] >>= \xs -> (,) xs `fmap` E.head Right ([1,5,3,6,10],Just 5) HTH, -- Felipe.

Thank you!
Working implementation is even more than I've expected.
2011/4/28 Felipe Almeida Lessa
On Thu, Apr 28, 2011 at 1:10 PM, Felipe Almeida Lessa
wrote: On Thu, Apr 28, 2011 at 12:09 PM, Felipe Almeida Lessa
wrote: I foresee one problem: what is the leftover of 'manyToOne xs' if each x in xs needs different lengths of input?
One possible untested-but-compiling solution: [snip]
Like I said, that manyToOne implementation isn't very predictable about leftovers. But I guess that if all your iteratees consume the same input OR if you don't care about leftovers, then it should be okay.
Sorry for replying to myself again. =)
I think you can actually give predictable semantics to manyToOne: namely, the leftovers from the last iteratee are returned. This new implementation should be better:
import Data.Monoid (mappend) import qualified Data.Enumerator as E
manyToOne :: Monad m => [E.Iteratee a m b] -> E.Iteratee a m [b] manyToOne is = E.Iteratee $ mapM E.runIteratee is >>= E.runIteratee . go where go [step] = fmap (:[]) (E.returnI step) go (E.Yield b _ : xs) = fmap (b:) (go xs) go (E.Error exc : _) = E.returnI (E.Error exc) go (E.Continue f : xs) = E.continue $ go' (E.Continue f : xs) go [] = return []
go' xs stream = manyToOne $ feed xs where feed [E.Yield b s] = [E.yield b (s `mappend` stream)] feed (E.Continue f : ys) = f stream : feed ys feed (step : ys) = E.returnI step : feed ys feed [] = []
With the same test as before:
*Main> E.run $ E.enumList 1 [5 :: Int, 6, 7] E.$$ manyToOne [return 1, maybe 2 id `fmap` E.head, return 3, maybe 4 id `fmap` (E.head >> E.head)] >>= \xs -> (,) xs `fmap` E.head Right ([1,5,3,6],Just 7) *Main> E.run $ E.enumList 10 [5 :: Int, 6, 7] E.$$ manyToOne [return 1, maybe 2 id `fmap` E.head, return 3, maybe 4 id `fmap` (E.head >> E.head)] >>= \xs -> (,) xs `fmap` E.head Right ([1,5,3,6],Just 7)
When the last iteratee doesn't consume anything:
*Main> E.run $ E.enumList 1 [5 :: Int, 6, 7] E.$$ manyToOne [return 1, maybe 2 id `fmap` E.head, return 3, maybe 4 id `fmap` (E.head >> E.head), return 10] >>= \xs -> (,) xs `fmap` E.head Right ([1,5,3,6,10],Just 5) *Main> E.run $ E.enumList 10 [5 :: Int, 6, 7] E.$$ manyToOne [return 1, maybe 2 id `fmap` E.head, return 3, maybe 4 id `fmap` (E.head >> E.head), return 10] >>= \xs -> (,) xs `fmap` E.head Right ([1,5,3,6,10],Just 5)
HTH,
-- Felipe.

On 28 April 2011 23:39, Dmitry Olshansky
Hello,
does somewhere exist function with type like this - manyToOne :: [Iteratee a m b] -> Iteratee a m [b] ?
I.e. I need to process one input through many Iteratees indepentently in constant space and collect results.
It is similar by type with sequenceM but as far as I understand sequenceM won't use the same input for all Iteratees.
Hi, this is also like the enumSequence Maciej Wos proposed: http://www.haskell.org/pipermail/haskell-cafe/2011-January/088319.html cheers, Conrad.
participants (3)
-
Conrad Parker
-
Dmitry Olshansky
-
Felipe Almeida Lessa