[Haskell-cafe] ByteStrings, FFI, iovec

Antoine Latter aslatter at gmail.com
Sat Mar 28 14:59:16 EDT 2009


Folks,

I'm putting together an FFI layer to a library which uses writev for
its IO, and so expects an array of iovec structs as an argument to one
of its calls.  for more information, check out "man writev"[1].

Since I'm already using Data.Binary, the writev call almost sounds
like a perfect match for lazy bytestrings, so I thought I'd put up
what I have for comments. I'm using c2hs[2].  The recursive nesting of
'withForeignPtr' put me off at first, but I thought I'd at least give
it a shot.  I haven't put this into practice yet, so it could be
buggy.  I'm more looking for comments on the approach.

Antoine

[1] http://linux.die.net/man/3/writev
[2] http://www.cse.unsw.edu.au/~chak/haskell/c2hs/

Foreign/IOVec.chs
>>>>>
-- -*-haskell-*-

module Foreign.IOVec
    (IOVec()
    ,withLazyByteString
    )
    where

import C2HS

import qualified Data.ByteString as S
import qualified Data.ByteString.Internal as S
import qualified Data.ByteString.Lazy as L

#include <sys/uio.h>

#c
typedef struct iovec hs_iovec;
#endc

{#pointer *hs_iovec as IOVec newtype#}

-- | This is intended for calling into something like writev.
-- But I suppose that nothing stops you from calling into
-- readv and blowing away the passed-in ByteString.
withLazyByteString :: L.ByteString -> (IOVec -> Int -> IO b) -> IO b
withLazyByteString b f =
    let bs = L.toChunks b
        num = length bs
    in allocaBytes (num * {#sizeof hs_iovec#}) $ \vecAry -> go vecAry 0 bs

   where go vecAry off [] = f (IOVec vecAry) off
         go vecAry off (b:bs) =

             let vec = vecAry `plusPtr` (off * {#sizeof hs_iovec#})
                 (fptr, bsOff, bsLen) = S.toForeignPtr b

             in withForeignPtr fptr $ \bsPtr -> do
                  {#set hs_iovec->iov_base#} vec $ castPtr $ bsPtr
`plusPtr` bsOff
                  {#set hs_iovec->iov_len#}  vec $ cIntConv bsLen
                  go vecAry (off+1) bs

<<<<<


More information about the Haskell-Cafe mailing list