2016-06-13 16:25:32 +02:00
|
|
|
{-# LANGUAGE StandaloneDeriving #-}
|
|
|
|
|
Finish up bindings to most core gRPC functions (#1)
* 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
* add requested comment
* remove slice_unref binding, use sliceFree when converting buffer to bytestring
2016-05-13 18:12:37 +02:00
|
|
|
module Network.GRPC.Unsafe.Slice where
|
|
|
|
|
|
|
|
#include <grpc/impl/codegen/slice.h>
|
|
|
|
#include <grpc_haskell.h>
|
|
|
|
|
|
|
|
import qualified Data.ByteString as B
|
|
|
|
import Foreign.C.String
|
|
|
|
import Foreign.C.Types
|
|
|
|
import Foreign.Ptr
|
|
|
|
|
|
|
|
-- | A 'Slice' is gRPC's string type. We can easily convert these to and from
|
|
|
|
-- ByteStrings. This type is a pointer to a C type.
|
|
|
|
{#pointer *gpr_slice as Slice newtype #}
|
|
|
|
|
2016-06-13 16:25:32 +02:00
|
|
|
deriving instance Show Slice
|
|
|
|
|
Finish up bindings to most core gRPC functions (#1)
* 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
* add requested comment
* remove slice_unref binding, use sliceFree when converting buffer to bytestring
2016-05-13 18:12:37 +02:00
|
|
|
-- TODO: we could also represent this type as 'Ptr Slice', by doing this:
|
|
|
|
-- newtype Slice = Slice {#type gpr_slice#}
|
|
|
|
-- This would have no practical effect, but it would communicate intent more
|
|
|
|
-- clearly by emphasizing that the type is indeed a pointer and that the data
|
|
|
|
-- it is pointing to might change/be destroyed after running IO actions. To make
|
|
|
|
-- the change, we would just need to change all occurrences of 'Slice' to
|
|
|
|
-- 'Ptr Slice' and add 'castPtr' in and out marshallers.
|
|
|
|
-- This seems like the right way to do it, but c2hs doesn't make it easy, so
|
|
|
|
-- maybe the established idiom is to do what c2hs does.
|
|
|
|
|
|
|
|
-- | Get the length of a slice.
|
2016-07-21 21:55:16 +02:00
|
|
|
{#fun unsafe gpr_slice_length_ as ^ {`Slice'} -> `CULong'#}
|
Finish up bindings to most core gRPC functions (#1)
* 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
* add requested comment
* remove slice_unref binding, use sliceFree when converting buffer to bytestring
2016-05-13 18:12:37 +02:00
|
|
|
|
|
|
|
-- | Returns a pointer to the start of the character array contained by the
|
|
|
|
-- slice.
|
2016-07-21 21:55:16 +02:00
|
|
|
{#fun unsafe gpr_slice_start_ as ^ {`Slice'} -> `Ptr CChar' castPtr #}
|
Finish up bindings to most core gRPC functions (#1)
* 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
* add requested comment
* remove slice_unref binding, use sliceFree when converting buffer to bytestring
2016-05-13 18:12:37 +02:00
|
|
|
|
2016-07-21 21:55:16 +02:00
|
|
|
{#fun unsafe gpr_slice_from_copied_buffer_ as ^ {`CString', `Int'} -> `Slice'#}
|
Finish up bindings to most core gRPC functions (#1)
* 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
* add requested comment
* remove slice_unref binding, use sliceFree when converting buffer to bytestring
2016-05-13 18:12:37 +02:00
|
|
|
|
|
|
|
-- | Properly cleans up all memory used by a 'Slice'. Danger: the Slice should
|
|
|
|
-- not be used after this function is called on it.
|
2016-07-21 21:55:16 +02:00
|
|
|
{#fun unsafe free_slice as ^ {`Slice'} -> `()'#}
|
Finish up bindings to most core gRPC functions (#1)
* 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
* add requested comment
* remove slice_unref binding, use sliceFree when converting buffer to bytestring
2016-05-13 18:12:37 +02:00
|
|
|
|
|
|
|
-- | Copies a 'Slice' to a ByteString.
|
|
|
|
-- TODO: there are also non-copying unsafe ByteString construction functions.
|
|
|
|
-- We could gain some speed by using them.
|
|
|
|
-- idea would be something :: (ByteString -> Response) -> IO () that handles
|
|
|
|
-- getting and freeing the slice behind the scenes.
|
|
|
|
sliceToByteString :: Slice -> IO B.ByteString
|
|
|
|
sliceToByteString slice = do
|
|
|
|
len <- fmap fromIntegral $ gprSliceLength slice
|
|
|
|
str <- gprSliceStart slice
|
|
|
|
B.packCStringLen (str, len)
|
|
|
|
|
|
|
|
-- | Copies a 'ByteString' to a 'Slice'.
|
|
|
|
byteStringToSlice :: B.ByteString -> IO Slice
|
2016-07-14 18:53:28 +02:00
|
|
|
byteStringToSlice bs = B.useAsCStringLen bs $ uncurry gprSliceFromCopiedBuffer
|