On Fri, Mar 20, 2009 at 07:42:28PM +0100, Nicolas Pouillard wrote:
> We have good news (nevertheless we hope) for all the lazy guys standing there.
> Since their birth, lazy IOs have been a great way to modularly leverage all 
> the
> good things we have with *pure*, *lazy*, *Haskell* functions to the real world
> of files.

Hey, that's really great! Even if I can't tell you that I used your
library and found out that it works fine, it sure looks handy.

I was reading the sources, and for 'interleaveHandles' you can
probably use forkIO. Internally GHC will use select whenever a forkIO
blocks on something. Probably telling the forkIO's to write on a Chan
would suffice, but something more elaborate to get as much data as
possible because of the Chan's overhead should be better, maybe block
with hWaitForInput and then use hGetBufNonBlocking? Something on the
lines the untested code below:

> import Control.Concurrent (forkIO)
> import Data.Char (chr)
> import Data.Function (fix)
> import Data.Word8 (Word8)
> import Foreign.Marshal.Alloc (allocaBytes)
> import Foreign.Storable (peekByteOf)
>
> interleaveHandlesHelper :: Handle -> Handle -> IO [Either [Char] [Char]]
> interleaveHandlesHelper h1 h2 = do chan <- newChan
>                                    forkIO $ forkFor Left  h1 chan
>                                    forkIO $ forkFor Right h2 chan
>                                    getThem chan
>     where
>       timeout = -1    -- block forever, that's what we want
>       bufSize = 4096  -- more? less?
>       forkFor tag h chan = allocaBytes bufSize $ \buf ->
>                            (fix $ \f -> do hWaitForInput h timeout
>                                            cnt <- hGetBufNonBlocking h buf 
> bufSize
>                                            readBuf buf cnt >>= writeChan chan 
> . Just . tag
>                                            f) `catchEOF` (writeChan chan 
> Nothing)
>       getThem chan = go 2 -- two is the number of handles
>           where go 0 = return []
>                 go n = unsafeInterleaveIO $ do -- lazy
>                          c <- readChan chan
>                          case c of
>                            Nothing -> go (n-1)
>                            Just d  -> (d:) `fmap` go n
>
> readBuf :: Ptr Word8 -> Int -> IO [Char]
> readBuf ptr cnt = mapM (toChar `fmap` peekByteOf ptr) [0..cnt-1]
>   where toChar = chr. fromIntegral -- maybe use Data.ByteString.Internal.w2c


Thanks!

--
Felipe.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to