[Haskell-cafe] Re: binary IO

Bulat Ziganshin bulatz at HotPOP.com
Wed Dec 28 05:16:43 EST 2005


Hello Peter,

Tuesday, December 27, 2005, 11:26:29 PM, you wrote:

PS> My guess is that you would learn more if _you_ would plug
PS> the different IO libraries into your test code. I'm certain

Peter, because you claimed that Haskell can be made as effective as C,
please help us :)

your BlockIO library is great, but it's usage is limited to very
specific sutuations - when we can save pass state between processing
of individual bytes

what for (de)serialization tasks? my best attempts is still 10x slower
than C version. can you roll up little prototype for such library or
just sketch an ideas so i can try to implement it?

it is also call to everyone - what is the key to efficient Binary lib?
you can see my current attempt in http://freearc.narod.ru/Binary.tar.gz

the key functions:

instance (MemoryStream h) => ByteStream (BufferedMemoryStream h) where
    vPutByte mem@(Buf h buf' pos' end') byte = do
        pos <- readPtr pos'
        end <- readPtr end'
        if (pos==end) then do
            sendCurrentBuffer mem
            receiveNextBuffer mem
            vPutByte mem byte
         else do
            writePtr pos' $! (pos+:1)
            writeByteAt pos $! (fromEnum byte)

    vGetByte mem@(Buf h buf' pos' end') = do
        pos <- readPtr pos'
        end <- readPtr end'
        if (pos==end) then do
            sendCurrentBuffer mem
            receiveNextBuffer mem
            vGetByte mem
         else do
            writePtr pos' $! (pos+:1)
            byte <- readByteAt pos
            return $! (toEnum byte)

and series of getWordXX/putWordXX in "class (ByteStream h) => BitStream h":

    putWord32 h w = do vPutByte h $! ( w `shiftR` 24)
                       vPutByte h $! ((w `shiftR` 16) .&. 0xff)
                       vPutByte h $! ((w `shiftR` 8)  .&. 0xff)
                       vPutByte h $! ( w              .&. 0xff)
    getWord32 h = do w1 <- vGetByte h
                     w2 <- vGetByte h
                     w3 <- vGetByte h
                     w4 <- vGetByte h
                     return $! ((w1 `shiftL` 24) .|.
                                (w2 `shiftL` 16) .|.
                                (w3 `shiftL`  8) .|.
                                (w4))

-- 
Best regards,
 Bulat                            mailto:bulatz at HotPOP.com





More information about the Haskell-Cafe mailing list