sequence and sequence_ for iteratees

Hello Cafe! I have written some iteratee functions that I found to be very very useful and I hope they will soon make it to the iteratee library. However, I'd like to get some feedback first, particularly about the error handling. I'm sending this here rather than to iteratee mailing list at projects.haskell.org because the latter is (and has been for a while!) down... Anyway, enumSequence and enumSequence_ are inspired by Prelude's sequence and sequence_. They are useful when one has to deal with several iteratees consuming the same data. For instance, one could use enumSequence as follows:
run $ joinIM $ enumPureNChunk [1..100] 3 $ enumSequence [I.head, I.head >>= \x -> I.head >>= \y -> return (x+y), I.last]
which produces: [1,3,100] Each iteratee in the list is given the same input stream. Also, enumSequence consumes as much of the stream as the iteratee in the list that consumes the most. In the above example there is no stream left after enumSequence finishes because I.last consumes everything. As an another example, enumSequence below consumes only the first two elements of the stream and the remainder is passed to stream2list:
run $ joinIM $ enumPureNChunk [1..10] 3 $ (enumSequence [I.head, I.head >> I.head] >> stream2list)
[3,4,5,6,7,8,9,10] The code for enumSequence is enclosed below (enumSequence_ is almost identical!) To make it complete though I should add some sort of error handling. I'm not quite sure however what would be the best thing to do. For instance, what should happen if the stream is finished, but one of the iteratees is not done yet? Should the whole enumSequence fail? Similarly, should the whole enumSequence fail if one of the iteratees throws an error? I guess throwing some sort of recoverable error could work. But I still need to figure out how to do that! -- Maciej ########## code ########## enumSequence :: forall m s a el . (Monad m, LL.ListLike s el, Nullable s) => [Iteratee s m a] -> Iteratee s m [a] enumSequence is = liftI step where step :: Stream s -> Iteratee s m [a] step s@(Chunk xs) | LL.null xs = liftI step | otherwise = do let is' = map (joinIM . enumPure1Chunk xs) is allDone <- lift (checkIfDone is') if allDone then uncurry idone =<< lift (collectResults is') else enumSequence (updateChunk s is') -- TODO: should return an error if not all iteratees are done step (EOF _) = uncurry idone =<< lift (collectResults . map (joinIM . enumEof) $ is) -- returns true if *all* iteratees are done; otherwise returns false checkIfDone :: [Iteratee s m a] -> m Bool checkIfDone = liftM and . mapM (\i -> runIter i onDone onCont) where onDone _ _ = return True onCont _ _ = return False -- returns a list of result values and the unconsumed part of the stream collectResults :: [Iteratee s m a] -> m ([a], Stream s) collectResults = liftM (id *** foldl1 shortest) . mapAndUnzipM (\i -> runIter i onDone onCont) where onDone a s = return (a,s) onCont _ _ = error "enumSequence: collectResults failed; all iteratees should be done" shortest :: Stream s -> Stream s -> Stream s shortest (Chunk xs) (Chunk ys) | LL.length xs > LL.length ys = Chunk ys | otherwise = Chunk xs shortest s@(EOF _) _ = s shortest _ s@(EOF _) = s -- iteratee in *done* state holds the unconsumed part of the chunk it -- was given; this chunk needs to be discarded when we move further in -- the stream updateChunk :: Stream s -> [Iteratee s m a] -> [Iteratee s m a] updateChunk s = map (\i -> joinIM $ runIter i (\a _ -> return $ idone a s) icontM)

I have small program UULib which i use for checking some timing information. When I compile with ghc 7 and profiling information I get the timings which are more or less what I expect. If I however recompile without profiling tome consumed goes up by a factor of 20! 1) Am I misinterpreting the results? 2) If not, does this look familiar to anyone? 3) If so, whether should I look first to see what is going on here? Doaitse dyn-81-64:ProgramTests doaitse$ ghc --make UULib [1 of 2] Compiling ParseInputs ( ParseInputs.hs, ParseInputs.o ) [2 of 2] Compiling Main ( UULib.hs, UULib.o ) Linking UULib ... dyn-81-64:ProgramTests doaitse$ time ./UULib 138000 real 0m9.101s user 0m9.048s sys 0m0.038s dyn-81-64:ProgramTests doaitse$ ghc --make -prof -auto-all -rtsopts UULib [1 of 2] Compiling ParseInputs ( ParseInputs.hs, ParseInputs.o ) [2 of 2] Compiling Main ( UULib.hs, UULib.o ) Linking UULib ... dyn-81-64:ProgramTests doaitse$ time ./UULib 138000 real 0m0.418s user 0m0.376s sys 0m0.038s dyn-81-64:ProgramTests doaitse$ time ./UULib +RTS -h -p 138000 real 0m0.457s user 0m0.397s sys 0m0.034s

On Thursday 20 January 2011 15:18:51, S. Doaitse Swierstra wrote:
I have small program UULib which i use for checking some timing information.
When I compile with ghc 7 and profiling information I get the timings which are more or less what I expect. If I however recompile without profiling tome consumed goes up by a factor of 20!
Perhaps profiling prevents the application of an optimisation which is in fact a pessimisation for your programme. Does looking at the generated Core reveal something? (if you make the code available, others could look too) What are the times when you compile with -O[2]?
1) Am I misinterpreting the results? 2) If not, does this look familiar to anyone? 3) If so, whether should I look first to see what is going on here?
Look at the Core, ask on glasgow-haskell-users/open a ticket so that you have a better chance of getting the attention of an expert (the GHC team don't regularly follow the cafe).

I have small program UULib which i use for checking some timing information. When I compile with ghc 7 and profiling information I get the timings which are more or less what I expect. If I however recompile without profiling tome consumed goes up by a factor of 20! 1) Am I misinterpreting the results? 2) If not, does this look familiar to anyone? 3) If so, whether should I look first to see what is going on here? Doaitse dyn-81-64:ProgramTests doaitse$ ghc --make UULib [1 of 2] Compiling ParseInputs ( ParseInputs.hs, ParseInputs.o ) [2 of 2] Compiling Main ( UULib.hs, UULib.o ) Linking UULib ... dyn-81-64:ProgramTests doaitse$ time ./UULib 138000 real 0m9.101s user 0m9.048s sys 0m0.038s dyn-81-64:ProgramTests doaitse$ ghc --make -prof -auto-all -rtsopts UULib [1 of 2] Compiling ParseInputs ( ParseInputs.hs, ParseInputs.o ) [2 of 2] Compiling Main ( UULib.hs, UULib.o ) Linking UULib ... dyn-81-64:ProgramTests doaitse$ time ./UULib 138000 real 0m0.418s user 0m0.376s sys 0m0.038s dyn-81-64:ProgramTests doaitse$ time ./UULib +RTS -h -p 138000 real 0m0.457s user 0m0.397s sys 0m0.034s
participants (4)
-
Daniel Fischer
-
Maciej Wos
-
S. Doaitse Swierstra
-
S. Doaitse Swierstra