[Haskell-cafe] Allocating a new ByteString
Tristan Seligmann
mithrandi at mithrandi.net
Mon Dec 22 22:48:31 UTC 2014
I'm calling a function by FFI that returns two strings by writing into
output buffers that you provide. The code I currently have looks like
this (minus some error handling):
> import qualified Data.ByteString as S
> import qualified Data.ByteString.Unsafe as SU
>
> import Foreign.C (CChar, CInt(..), CSize(..))
> import Foreign.ForeignPtr (mallocForeignPtrBytes, withForeignPtr)
> import Foreign.Ptr (Ptr)
> import System.IO.Unsafe (unsafePerformIO)
>
> seed_keypair :: S.ByteString -> (S.ByteString, S.ByteString)
> seed_keypair seed | S.length seed /= signSeed = error "seed has incorrect length"
> | otherwise = unsafePerformIO $ do
> pk <- mallocForeignPtrBytes signPK
> sk <- mallocForeignPtrBytes signSK
> SU.unsafeUseAsCString seed $ \pseed ->
> withForeignPtr pk $ \ppk ->
> withForeignPtr sk $ \psk -> do
> 0 <- c_sign_seed_keypair ppk psk pseed
> bpk <- S.packCStringLen (ppk, signPK)
> bsk <- S.packCStringLen (psk, signSK)
> return (bpk, bsk)
>
> foreign import ccall "crypto_sign_seed_keypair"
> c_sign_seed_keypair :: Ptr CChar -> Ptr CChar -> Ptr CChar -> IO CInt
However, this needlessly makes a copy of the output buffers to create
the final result. What I really want to do is just write the string
directly into a buffer allocated and used by a new ByteString; is
there some way to accomplish this?
(Any other comments about what I'm doing would also be appreciated,
this happens to be my first attempt at using FFI!)
--
mithrandi, i Ainil en-Balandor, a faer Ambar
More information about the Haskell-Cafe
mailing list