[Haskell-cafe] Re: Fwd: Semantics of iteratees, enumerators, enumeratees?

John Lato jwlato at gmail.com
Tue Sep 7 07:45:42 EDT 2010


At first I regarded this as simply a bug in the Iteratee.map definition, but
like Ben, it's started to bother me a lot.  I think this is precisely the
sort of issue a proper denotational semantics would fix.

Unfortunately the only general solution I see is to abandon chunking and
work strictly element-wise.  I say unfortunately because my current best
implementation is about 5 times slower than the main tree.  I'm open to
ideas.

John


> From: Ben <midfield at gmail.com>
>
> Sorry to be late coming into this conversation.....
>
> Something that has bothered me (which I have mentioned to John Lato
> privately) is that it is very easy to write non-compositional code due
> to the chunking.  For example, there is a standard function
>
> map :: (a -> b) -> Enumeratee a b c
>
> whose meaning I hope is clear : use the function to transform the type
> of a stream and pass it to an iteratee.  However last I checked the
> versions provided in both the iteratee and enumerator packages fail to
> satisfy the equation
>
> map f (it1 >> it2) == (map f it1) >> (map f it 2)
>
> because of chunking, essentially.  You can check this with f == id and
> it1 and it2 are head:
>
> let r = runIdentity . runIteratee
>
> runIdentity $ run $ enumList 10 [1..100] $ r $ joinI $ map id $ r (head >>
> head)
> --> Right (Just 2)
>
> runIdentity $ run $ enumList 10 [1..100] $ r $ joinI $ (map id $ r
> head) >> (map id $ r head)
> --> Right (Just 11)
>
> It is possible to fix this behavior, but it complicates the "obvious"
> definitions a lot.
>
> B
>
> On Wed, Sep 1, 2010 at 5:10 AM, Heinrich Apfelmus
> <apfelmus at quantentunnel.de> wrote:
> > Tilo Wiklund wrote:
> >>
> >> Daniel Fischer wrote:
> >>>
> >>> [...]
> >>> Well, I just gave an example where one would want chunking for reasons
> >>> other than performance. That iteratees don't provide the desired
> >>> functionality is a different matter.
> >>> [...]
> >>
> >> In the case of hashing, wouldn't it be more reasonable to consider
> >> iterators over streams of fixed (or at least predictable) sized chunks
> >> (where a set of chunks can themselves be chunked), with the chunking
> >> behaviour being given by another iteratee over the original stream?
> >>
> >> It seems to me that one of the major points of iteratees is to provide
> >> an abstraction from the kind of chunking irrelevant to the parsing
> >> logic, otherwise I fail to see any difference (at least relevant to
> >> chunking) to plain strict IO.
> >
> > I thought so, too, but I was informed[1] that iteratees are just a small
> > step up the abstraction ladder. The difference compared to an ordinary
> file
> >  Handle  is that you can now reuse one and the same iteratee for reading
> > from a  String , for instance, without changing the source code of the
> > iteratee.
> >
> > Furthermore, iteratees can be suspended, which facilities resource
> > management like closing files handles after they've been read.
> >
> >  [1]:
> >
> http://www.reddit.com/r/haskell/comments/ar4wb/understanding_iteratees/c0j0f3r
> >
> >
> >
> > Regards,
> > Heinrich Apfelmus
> >
> > --
> > http://apfelmus.nfshost.com
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100907/9415b97c/attachment.html


More information about the Haskell-Cafe mailing list