Hi Max,

How about this function?

    processFiles :: IterateeG [] String m a -> [FilePath] -> m
(IterateeG [] String m a)
    processFiles = foldM (\i fp -> fileDriver fp (convStream decodeStrings i)

The nice thing about an enumeratee is that you can just run the outer
iteratee (fileDriver does this implicitly) and have the inner iteratee
returned.  You can then use it as input to a new
enumerator/enumeratee.

In the case where you want to treat multiple files as one long stream
of data, there's another approach (although I think the above will
work too).  If you define
    enumFile :: Monad m => FilePath -> EnumeratorGMM s el m a
(which really should be in the library), which can be written
(restricted-to-IO) as:

    enumFile :: FilePath -> IterateeG s el IO a -> IO (IterateeG s el IO a)
    enumFile fp iter = bracket (openBinaryFile fp ReadMode) (flip
enumHandle iter) (hClose)

Now you can combine these file enumerators with (>.) like this:

    enumMyFiles :: [FilePath] -> EnumeratorGMM s el IO a
    enumMyFiles = foldr (>.) enumEof . map enumFile

I like this function, but nothing delimits the files in the stream, so
it's not always applicable.

Does this help?

Best,
John

On Mon, Jul 26, 2010 at 5:19 AM, Max Cantor <mxcan...@gmail.com> wrote:
> I have a series of files with binary encoded data in them, and want to create 
> an enumerator iterates on the first element at the front of all the files.  
> Something like the pseudocode: return . minimum =<< mapM (fmap (heads . 
> lines) readFile)  listOfFileNames
>
> I can use convStream to create an enumerator which runs iteratees on each 
> tuple in a single file:
>
> (convStream decodeStrings) :: Monad m => IterateeG [] String m a -> IterateeG 
> WrappedByteString Word8 m (IterateeG [] MyDataType m a)
>
> or, with the EnumerateeGMM tysyn:
>
> (convStream decodeStrings) :: Monad m => EnumerateeGMM WrappedByteString 
> Word8 [] String m a
>
> My question is if there is a simple way to combine the Enumeratees to 
> enumerate on a set of files or if I have to write an enumerator from scratch.
>
> Thank you in advance,
> Max
>
> P.S. John, apologies for the duped email, sent from the wrong address by 
> mistake.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to