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

Nicolas Pouillard nicolas.pouillard at gmail.com
Mon Aug 23 09:02:53 EDT 2010


On Mon, 23 Aug 2010 14:38:29 +0200, Heinrich Apfelmus <apfelmus at quantentunnel.de> wrote:
> Luke Palmer wrote:
> > Heinrich Apfelmus wrote:
> >> Conal Elliott wrote:
> >>> For anyone interested in iteratees (etc) and not yet on the iteratees
> >>> mailing list.
> >>>
> >>> I'm asking about what iteratees *mean* (denote), independent of the
> >>> various implementations.
> >>
> >> In my world view, iteratees are just a monad M with a single operation
> >>
> >>    symbol :: M Char
> >>
> >> that reads the next symbol from an input stream.
> > 
> > So perhaps this could be a reasonable semantics?
> > 
> > Iteratee a = [Char] -> Maybe (a, [Char])
> >            = MaybeT (State [Char]) a
> > 
> > symbol [] = Nothing
> > symbol (c:cs) = Just (c, cs)
> > 
> > I'm not experienced with iteratees. Does this miss something?
> 
>  From a purely denotational point of view, that's a reasonable semantics.
> 
> However, and that's the main point, with this particular semantics, it 
> is impossible to implement
> 
>      runHandle :: M a -> Handle -> IO a
> 
> without using  unsafeInterleaveIO . Typical implementations of iteratees 
> do make that possible, by being able to suspend the iteratee after 
> feeding it a character.
> 
> 
> There are also enumerators and enumeratees. I think that
> 
>      purpose of enumerator =
> 	run an iteratee on multiple sources
>          (i.e. first part of the input from a  Handle ,
>            second part from a  String )

I would say more simply that an enumerator is a data-producer (or source).
Although it is a producer defined as a consummer (or sink) feeder.

An iteratee is thus the consummer. It is defined as an action asking either
for more food or producing a value and a food left over

-- ignoring errors and over-simplifing Stream as Maybe
data Step a b = Continue (Maybe a -> IO (Step a b))
              | Yield b (Maybe a)

type Iteratee a b = IO (Step a b)

-- the most important case is when getting Continue as input:
-- type Enumerator a b = (Maybe a -> IO (Step a b)) -> IO (Step a b)
type Enumerator a b = Step a b -> IO (Step a b)

Note that I'm far from an expert on Iteratee but I start to get some intuitions
out of it.

-- 
Nicolas Pouillard
http://nicolaspouillard.fr


More information about the Haskell-Cafe mailing list