[Haskell-cafe] Re: [Haskell] installing streams library

Bulat Ziganshin bulat.ziganshin at gmail.com
Sun May 28 06:44:37 EDT 2006


Hello Jeremy,

Sunday, May 28, 2006, 1:29:02 AM, you wrote:
>> can i include your work in the library itself?
> Absolutely.
thanks

>> is it better to include 'debian' directory to my archive or left
>> this to the debian packagers?

> If someone volunteers to maintain the package -- then it is probably

afaiu, you say about maintaining their debian ports? it seems that i
should include these files now and omit them when someone will start
to maintain the package?

> would be useful to provide the debian directory (with a disclaimer) so

what disclaimer?


> To get them into BDB I need to convert the haskell data structure into
> a C structure that looks like this:

> struct __db_dbt {
>         void     *data;                 /* Key/data */
>         u_int32_t size;                 /* key/data length */
> };


> Currently I am doing it like this -- but this will clearly fail if the
> serialized data structure is longer than 512 bytes...

> withDBT :: (Binary a) => a -> (Ptr DBT -> IO b) -> IO b
> withDBT thedata f =
>     allocaBytes #{size DBT} $ \dbtPtr ->
>         allocaBytes 512 $ \dataPtr ->
>             do h <- openMemBuf dataPtr 512
>                withByteAlignedLE h $ flip put_ thedata
>                wrote <- vTell h
>                vClose h
>                #{poke DBT, data} dbtPtr (castPtr dataPtr)
>                #{poke DBT, size} dbtPtr ((fromIntegral wrote) :: Int)
>                f dbtPtr

i will prefer to split it into two parts. and, DBD-interfacing part can
be also implemented using binary i/o:

 withDBT00 :: Ptr a -> Int -> (Ptr DBT -> IO b) -> IO b
 withDBT00 f buf size =
             do h <- createMemBuf 20 >>= openByteAlignedLE
                put_      h buf
                putWord32 h size
                vRewind h
                (dbt,_) <- vReceiveBuf h
                result <- f dbt
                vClose h
                return result

withDBT f thedata = encodeMemBufLE (withDBT00 f) thedata



> I don't really need the file-system interface for this project -- what
> would be nice is something like 'withCStringLen' and 'peekCString' for
> the encode/decode functions:

> type PtrLen a = (Ptr a, Int)
> encodePtrLen :: (Binary a) => a -> (PtrLen a -> IO b) -> IO b
> decodePtr :: (Binary a) => Ptr a -> IO a

encodeMemBufLE f thedata =
             do h <- createMemBuf 512 >>= openByteAlignedLE
                put_ h thedata
                vRewind h
                (buf,size) <- vReceiveBuf h
                result <- f buf size
                vClose h
                return result
                
decodeMemBufLE buf size =
             do h <- openMemBuf buf size >>= openByteAlignedLE
                result <- get h
                vClose h
                return result
             
but it will work only with Streams 0.1. you have spotted the problem
that there is no official way to get access to the whole buffer
contents if buffer was created with createMemBuf.

> I could simulate this by using 'encode' to convert the data structure
> to a String and then use 'withCStringLen' to get the pointer and
> length -- but having the intermediate String seems like it could be a
> big performance hit.

Strings are slow by itself and moreover 'encode' has O(n^2) complexity

> Two alternative ideas are:

>  (1) accurately pre-calculate the size of the serialized structure and
>      allocate the correct amount of memory from the start

it's good idea to have 'binarySize :: Binary a => a->Int' function,
although using it will halve the speed, so for you it's not the best
solution

>  (2) start with a 'guess' and realloc the memory if the initial guess
>      is too small.

createMemBuf does exactly this :)  it's for why the whole Streams part
exist. actually i have started with trivial

instance ByteStream Handle where
    vPutByte h n = do hPutChar h (chr (fromEnum n))
    vGetByte h   = do c <- hGetChar h
                      return $! (toEnum (ord c))

and only after Binary part was enough matured, i goes to adding all those
fancy Stream features

> I have not looked at the library exhaustively, so if there is already
> a good way to do this, let me know.

the way exist but it's not guaranteed by library interface and uses my
knowledge of library internals. i will add interface which guarantees
access to full buffer's contents. after that, 'encodeMemBufLE' can be
written using official library capabilities. i will also add
encodeMemBuf*/decodeMemBuf* to the lib, although i'm not sure that
these functions are universal enough


-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



More information about the Haskell-Cafe mailing list