gRPC-haskell/core/src/Network/GRPC/Unsafe/ByteBuffer.chs

98 lines
3.7 KiB
Plaintext
Raw Normal View History

{-# LANGUAGE StandaloneDeriving #-}
module Network.GRPC.Unsafe.ByteBuffer where
#include <grpc/grpc.h>
#include <grpc/slice.h>
#include <grpc/impl/codegen/compression_types.h>
#include <grpc/slice_buffer.h>
#include <grpc_haskell.h>
{#import Network.GRPC.Unsafe.Slice#}
{#import Network.GRPC.Unsafe.ChannelArgs#}
import Control.Exception (bracket)
import qualified Data.ByteString as B
import Foreign.Ptr
import Foreign.C.Types
import Foreign.Storable
-- | Represents a pointer to a gRPC byte buffer containing 1 or more 'Slice's.
-- Must be destroyed manually with 'grpcByteBufferDestroy'.
{#pointer *grpc_byte_buffer as ByteBuffer newtype #}
deriving instance Show ByteBuffer
--Trivial Storable instance because 'ByteBuffer' type is a pointer.
instance Storable ByteBuffer where
sizeOf (ByteBuffer r) = sizeOf r
alignment (ByteBuffer r) = alignment r
peek p = fmap ByteBuffer (peek (castPtr p))
poke p (ByteBuffer r) = poke (castPtr p) r
--TODO: When I switched this to a ForeignPtr with a finalizer, I got errors
--about freeing un-malloced memory. Calling the same destroy function by hand
--works fine in the same code, though. Until I find a workaround, going to free
--everything by hand.
-- | Represents a pointer to a ByteBufferReader. Must be destroyed manually with
-- 'byteBufferReaderDestroy'.
{#pointer *grpc_byte_buffer_reader as ByteBufferReader newtype #}
-- | Creates a pointer to a 'ByteBuffer'. This is used to receive data when
-- creating a GRPC_OP_RECV_MESSAGE op.
{#fun unsafe create_receiving_byte_buffer as ^ {} -> `Ptr ByteBuffer' id#}
{#fun unsafe destroy_receiving_byte_buffer as ^ {id `Ptr ByteBuffer'} -> `()'#}
withByteBufferPtr :: (Ptr ByteBuffer -> IO a) -> IO a
withByteBufferPtr
= bracket createReceivingByteBuffer destroyReceivingByteBuffer
-- | Takes an array of slices and the length of the array and returns a
-- 'ByteBuffer'.
{#fun grpc_raw_byte_buffer_create as ^ {`Slice', `CULong'} -> `ByteBuffer'#}
{#fun grpc_raw_compressed_byte_buffer_create as ^
{`Slice', `CULong', `CompressionAlgorithm'} -> `ByteBuffer'#}
{#fun unsafe grpc_byte_buffer_copy as ^ {`ByteBuffer'} -> `ByteBuffer'#}
{#fun unsafe grpc_byte_buffer_length as ^ {`ByteBuffer'} -> `CULong'#}
{#fun unsafe grpc_byte_buffer_destroy as ^ {`ByteBuffer'} -> `()'#}
{#fun unsafe byte_buffer_reader_create as ^ {`ByteBuffer'} -> `ByteBufferReader'#}
{#fun unsafe byte_buffer_reader_destroy as ^ {`ByteBufferReader'} -> `()'#}
{#fun grpc_byte_buffer_reader_next as ^
{`ByteBufferReader', `Slice'} -> `CInt'#}
-- | Returns a 'Slice' containing the entire contents of the 'ByteBuffer' being
-- read by the given 'ByteBufferReader'.
{#fun unsafe grpc_byte_buffer_reader_readall_ as ^ {`ByteBufferReader'} -> `Slice'#}
{#fun unsafe grpc_raw_byte_buffer_from_reader as ^
{`ByteBufferReader'} -> `ByteBuffer'#}
withByteStringAsByteBuffer :: B.ByteString -> (ByteBuffer -> IO a) -> IO a
withByteStringAsByteBuffer bs f = do
bracket (byteStringToSlice bs) freeSlice $ \slice -> do
bracket (grpcRawByteBufferCreate slice 1) grpcByteBufferDestroy f
-- Creates a 'ByteBuffer'. We also return the slice we needed to allocate to
-- create it. It is the caller's responsibility to free both when finished using
-- the byte buffer. In most cases, one should prefer to use
-- 'withByteStringAsByteBuffer' if possible.
createByteBuffer :: B.ByteString -> IO (ByteBuffer, Slice)
createByteBuffer bs = do
slice <- byteStringToSlice bs
bb <- grpcRawByteBufferCreate slice 1
return (bb, slice)
Begin safe low-level Haskell layer (#7) * grpc_server_request_call * basic slice functionality * rename function to emphasize side effects * add docs * ByteBuffer function bindings * replace unsafeCoerce with more specific function, add docs, tests. * add newtypes for Tag and Reserved void pointers * manually fix request_registered_call binding * use nocode keyword to fix Ptr () problems * decouple copying Slice from freeing slice * Add time ops * remove nocode decls * Start Op module, fix c2hs preprocessing order * metadata manipulation operations * metadata free function, test * helper functions for constructing ops of each type * bindings for op creation functions * finish up Op creation functions, implement Op destruction, add docs. * tweak documentation * rework Op creation functions to work with an array of ops, for ease of use with grpc_call_start_batch * forgot to change return types * wrap hook lines, fix types to op creation functions * implement part of the payload test * hideous, but working, end to end test * bindings for connectivity state checks, split test into two threads * various cleanup * rename Core to Unsafe for emphasis, clean up tests more * begin safe low-level facilities * begin completion queue and server stuff * Finish server start/stop, cq start/stop, add tests * facilities for safely executing op batches * reorganize LowLevel modules, begin explicit export list * client functionality, stub payload test, various refactors * tweak cabal file, add test * add more documentation * doc tweaks * begin refactor to improve CompletionQueue safety * export only thread-safe CQ functions, add registered call creation and other CQ utilities * begin refactor to use GRPCIO monad, fix missing push semaphore, fix mem leak in server calls * switch to explicit Either where needed * add crashing tests, continue fleshing out serverHandleNormalCall * fix haddock error, finish first draft of request handling function * reduce GHC warnings * non-registered client request helpers * initial request/response test working * don't pass tags around; generate where needed * server call bracket functions * correct order of semaphore acquisition and shutdown check * simple debug flag logging, simplify Call type * fix various registered method issues (but still not working) * cleanup * delete old code * remove old todo * use MetadataMap synonym pervasively * more comments * update TODOs * tweak safety caveat * docs tweaks * improve haddocks * add casts to eliminate clang warnings, remove unused function * update options to eliminate cabal warnings * remove outdated todo * remove unneeded exports from CompletionQueue * rename to GRPCIOCallError, re-add create/shutdown exports (needed for Server module) * newtypes for hosts and method names * more newtypes * more debug logging * Fix flag name collision * instrument uses of free * more debug * switch to STM for completion queue stuff * reduce warnings * more debugging, create/destroy call tests * refactor, fix failure cleanup for server call creation. More tests passing. * formatting tweaks
2016-05-24 22:34:50 +02:00
copyByteBufferToByteString :: ByteBuffer -> IO B.ByteString
copyByteBufferToByteString bb = do
bracket (byteBufferReaderCreate bb) byteBufferReaderDestroy $ \bbr -> do
bracket (grpcByteBufferReaderReadall bbr) freeSlice sliceToByteString