[Haskell] ANNOUNCE: coroutine-enumerator

Mario Blažević mblazevic at stilo.com
Thu Nov 4 22:58:03 EDT 2010


The newly released coroutine-enumerator package can be used as a bridge
between the enumerator and monad-coroutine packages. It provides two-way
conversion functions between an Iteratee and an Await-suspending coroutine,
and also between an Enumerator and a Yield-suspending coroutine.

As a little example, the following program combines the http-enumerator,
monad-coroutine, and SCC packages using the coroutine-enumerator package to
print out all lines from the Hackage database containing substring
"enumerator":

> import Control.Exception.Base (SomeException)
> import Control.Monad.Trans.Class (lift)
>
> import Data.ByteString (ByteString)
> import Data.Text.Encoding (decodeUtf8)
>
> import Network.HTTP.Enumerator
>
> import Control.Monad.Coroutine
> import Control.Monad.Coroutine.SuspensionFunctors
> import Control.Monad.Coroutine.Nested
> import Control.Monad.Coroutine.Enumerator
>
> import Control.Concurrent.SCC.Sequential
>
> main = httpRedirect (\_ _-> coroutineIteratee consumer) =<< parseUrl
address
>
> address = "http://hackage.haskell.org/packages/archive/pkg-list.html"
>
> consumer :: Coroutine (Await [ByteString]) IO (Either SomeException ((),
[ByteString]))
> consumer = pipe translator (consume worker) >> return (Right ((), []))
>
> translator :: Functor f => Sink IO (EitherFunctor (Await [a]) f) a ->
Coroutine (EitherFunctor (Await [a]) f) IO ()
> translator sink = do chunks <- liftParent await
>                      if null chunks
>                         then lift (putStrLn "END")
>                         else putList chunks sink >> translator sink
>
> worker :: Consumer IO ByteString ()
> worker = toChars >-> foreach (line `having` substring "enumerator")
>                              (append (fromList "\n") >-> toStdOut)
>                              suppress
>
> toChars :: Monad m => Transducer m ByteString Char
> toChars = oneToOneTransducer decodeUtf8 >-> coerce


Alternatively, the worker coroutine can parse the XML database and print out
all elements whose any attribute value contains the substring "enumerator":

> worker = toChars
>          >-> parseXMLTokens
>          >-> foreach (xmlElementHavingTagWith (xmlAttributeValue `having`
substring "enumerator")
>                       `nestedIn` xmlElementContent)
>                      (coerce >-> toStdOut)
>                      suppress
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell/attachments/20101104/b9abc636/attachment.html


More information about the Haskell mailing list