Excerpts from Jinjing Wang's message of Thu Jan 14 01:28:31 +0100 2010:
| The hyena backend is essentially just a translator between hack and
| wai, i failed to finished it since I can't understand iteratee
| (seriously) and eventually got distracted  ...

If I have well understood you miss a function to convert an enumerator
to a list.

What about this code?

> import qualified Data.ByteString.Lazy.Char8 as S
> import Control.Concurrent (forkIO)
> import Control.Concurrent.Chan (newChan,writeChan,getChanContents)
>
> type Enumerator = forall a. (a -> S.ByteString -> IO (Either a a)) -> a -> IO 
> a
>
> enumToList :: Enumerator -> IO [S.ByteString]
> enumToList e = do ch <- newChan
>                   _  <- forkIO $ e (writer ch) ()
>                   getChanContents ch
>   where writer ch () chunk = do writeChan ch chunk
>                                 return (Right ())

Best regards,

-- 
Nicolas Pouillard
http://nicolaspouillard.fr
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to