core: optimize C apis (#3100)

* core: optimize C apis

* more

* fix tests

* use pokeByteOff

* write lazy bytestring to buffer without conversion to strict

* avoid conversion of JSON to strict bytestrings
This commit is contained in:
Evgeny Poberezkin 2023-09-22 13:45:16 +01:00 committed by GitHub
parent 08ea5dc2e7
commit b3e880ee54
No known key found for this signature in database
GPG key ID: 4AEE18F83AFDEB23
5 changed files with 77 additions and 52 deletions

View file

@ -1,19 +1,48 @@
{-# LANGUAGE LambdaCase #-}
module Simplex.Chat.Mobile.Shared where
import qualified Data.ByteString as B
import Data.ByteString.Internal (ByteString (PS), memcpy)
import Data.ByteString.Internal (ByteString (..), memcpy)
import qualified Data.ByteString.Lazy as LB
import qualified Data.ByteString.Lazy.Internal as LB
import Foreign.C (CInt, CString)
import Foreign (Ptr, Word8, newForeignPtr_, plusPtr)
import Foreign.ForeignPtr.Unsafe
import Foreign
type CJSONString = CString
type JSONByteString = LB.ByteString
getByteString :: Ptr Word8 -> CInt -> IO ByteString
getByteString ptr len = do
fp <- newForeignPtr_ ptr
pure $ PS fp 0 $ fromIntegral len
pure $ BS fp $ fromIntegral len
{-# INLINE getByteString #-}
putByteString :: Ptr Word8 -> ByteString -> IO ()
putByteString ptr bs@(PS fp offset _) = do
let p = unsafeForeignPtrToPtr fp `plusPtr` offset
memcpy ptr p $ B.length bs
putByteString ptr (BS fp len) =
withForeignPtr fp $ \p -> memcpy ptr p len
{-# INLINE putByteString #-}
putLazyByteString :: Ptr Word8 -> LB.ByteString -> IO ()
putLazyByteString ptr = \case
LB.Empty -> pure ()
LB.Chunk ch s -> do
putByteString ptr ch
putLazyByteString (ptr `plusPtr` B.length ch) s
newCStringFromBS :: ByteString -> IO CString
newCStringFromBS s = do
let len = B.length s
buf <- mallocBytes (len + 1)
putByteString buf s
pokeByteOff buf len (0 :: Word8)
pure $ castPtr buf
newCStringFromLazyBS :: LB.ByteString -> IO CString
newCStringFromLazyBS s = do
let len = fromIntegral $ LB.length s
buf <- mallocBytes (len + 1)
putLazyByteString buf s
pokeByteOff buf len (0 :: Word8)
pure $ castPtr buf