Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type BufferSize = Sum Int32
- type Position = Int32
- data FBState = FBState {
- builder :: !Builder
- bufferSize :: !BufferSize
- maxAlign :: !(Max Alignment)
- cache :: !(Map ByteString Position)
- newtype WriteTableField = WriteTableField {
- unWriteTableField :: State FBState (FBState -> FBState)
- newtype WriteStruct a = WriteStruct {}
- newtype WriteTable a = WriteTable (State FBState Position)
- data WriteUnion a = WriteUnion {
- wuUnionType :: !Word8
- wuUnionValue :: !(State FBState Position)
- encode :: WriteTable a -> ByteString
- encodeState :: FBState -> WriteTable a -> ByteString
- encodeWithFileIdentifier :: forall a. HasFileIdentifier a => WriteTable a -> ByteString
- encodeStateWithFileIdentifier :: FBState -> FileIdentifier -> WriteTable a -> ByteString
- write :: Int32 -> Builder -> FBState -> FBState
- writeInt32 :: Int32 -> FBState -> FBState
- writeFileIdentifier :: FileIdentifier -> FBState -> FBState
- missing :: WriteTableField
- deprecated :: WriteTableField
- optional :: (a -> WriteTableField) -> Maybe a -> WriteTableField
- optionalDef :: Eq a => a -> (a -> WriteTableField) -> Maybe a -> WriteTableField
- writeWord8TableField :: Word8 -> WriteTableField
- writeWord16TableField :: Word16 -> WriteTableField
- writeWord32TableField :: Word32 -> WriteTableField
- writeWord64TableField :: Word64 -> WriteTableField
- writeInt8TableField :: Int8 -> WriteTableField
- writeInt16TableField :: Int16 -> WriteTableField
- writeInt32TableField :: Int32 -> WriteTableField
- writeInt64TableField :: Int64 -> WriteTableField
- writeFloatTableField :: Float -> WriteTableField
- writeDoubleTableField :: Double -> WriteTableField
- writeBoolTableField :: Bool -> WriteTableField
- writeTextTableField :: Text -> WriteTableField
- writeTableTableField :: WriteTable a -> WriteTableField
- writeStructTableField :: forall a. IsStruct a => WriteStruct a -> WriteTableField
- writeStructTableField' :: Alignment -> InlineSize -> Builder -> WriteTableField
- writeUnionTypesVectorTableField :: WriteVector (WriteUnion a) -> WriteTableField
- writeUnionValuesVectorTableField :: WriteVector (WriteUnion a) -> WriteTableField
- writeUnionTypeTableField :: WriteUnion a -> WriteTableField
- writeUnionValueTableField :: WriteUnion a -> WriteTableField
- writeUnion :: Word8 -> WriteTable a -> WriteUnion b
- vtable :: [Word16] -> Word16 -> ByteString
- writeTable :: [WriteTableField] -> WriteTable a
- class WriteVectorElement a where
- data WriteVector a
- fromMonoFoldable :: (MonoFoldable mono, Element mono ~ a) => Int32 -> mono -> WriteVector a
- fromMonoFoldable' :: (WriteVectorElement a, MonoFoldable mono, Element mono ~ a) => mono -> WriteVector a
- fromList :: WriteVectorElement a => Int32 -> [a] -> WriteVector a
- fromList' :: WriteVectorElement a => [a] -> WriteVector a
- singleton :: WriteVectorElement a => a -> WriteVector a
- empty :: WriteVectorElement a => WriteVector a
- newtype FromFoldable f a = FromFoldable (f a)
- fromFoldable :: (WriteVectorElement a, Foldable f) => Int32 -> f a -> WriteVector a
- fromFoldable' :: (WriteVectorElement a, Foldable f) => f a -> WriteVector a
- fromByteString :: ByteString -> WriteVector Word8
- fromLazyByteString :: ByteString -> WriteVector Word8
- inlineVector :: (MonoFoldable mono, Element mono ~ a) => (a -> Builder) -> Alignment -> InlineSize -> Int32 -> mono -> WriteTableField
- data TextInfos = TextInfos ![TextInfo] !BufferSize
- data TextInfo = TextInfo {}
- data OffsetInfo = OffsetInfo {}
- data TableInfo = TableInfo {
- tiState :: !FBState
- tiTablePositions :: ![Position]
- data Vecs a = Vecs ![Word8] ![State FBState Position]
- data UnionTableInfo = UnionTableInfo {
- utiState :: !FBState
- utiTablePositions :: ![Position]
- calcPadding :: Alignment -> Int32 -> BufferSize -> Int32
- alignTo :: Alignment -> Int32 -> FBState -> FBState
- uoffsetFromHere :: State FBState (FBState -> FBState)
- uoffsetFrom :: Position -> FBState -> FBState
- utf8length :: Text -> Int32
Documentation
type BufferSize = Sum Int32 Source #
type Position = Int32 Source #
The position of something in a buffer, expressed as the number of bytes counting from the end.
FBState | |
|
newtype WriteTableField Source #
newtype WriteStruct a Source #
A struct to be written to a flatbuffer.
Instances
IsStruct a => WriteVectorElement (WriteStruct a) Source # | |
Defined in FlatBuffers.Internal.Write data WriteVector (WriteStruct a) Source # fromMonoFoldable :: (MonoFoldable mono, Element mono ~ WriteStruct a) => Int32 -> mono -> WriteVector (WriteStruct a) Source # | |
newtype WriteVector (WriteStruct a) Source # | |
Defined in FlatBuffers.Internal.Write |
newtype WriteTable a Source #
A table to be written to a flatbuffer.
Instances
WriteVectorElement (WriteTable a) Source # | |
Defined in FlatBuffers.Internal.Write data WriteVector (WriteTable a) Source # fromMonoFoldable :: (MonoFoldable mono, Element mono ~ WriteTable a) => Int32 -> mono -> WriteVector (WriteTable a) Source # | |
newtype WriteVector (WriteTable a) Source # | |
Defined in FlatBuffers.Internal.Write |
data WriteUnion a Source #
A union to be written to a flatbuffer.
WriteUnion | |
|
Instances
WriteVectorElement (WriteUnion a) Source # | |
Defined in FlatBuffers.Internal.Write data WriteVector (WriteUnion a) Source # fromMonoFoldable :: (MonoFoldable mono, Element mono ~ WriteUnion a) => Int32 -> mono -> WriteVector (WriteUnion a) Source # | |
data WriteVector (WriteUnion a) Source # | |
Defined in FlatBuffers.Internal.Write |
encode :: WriteTable a -> ByteString Source #
Serializes a flatbuffer table as a lazy ByteString
.
encodeState :: FBState -> WriteTable a -> ByteString Source #
encodeWithFileIdentifier :: forall a. HasFileIdentifier a => WriteTable a -> ByteString Source #
Serializes a flatbuffer table as a lazy ByteString
and adds a File Identifier.
encodeStateWithFileIdentifier :: FBState -> FileIdentifier -> WriteTable a -> ByteString Source #
writeFileIdentifier :: FileIdentifier -> FBState -> FBState Source #
optional :: (a -> WriteTableField) -> Maybe a -> WriteTableField Source #
optionalDef :: Eq a => a -> (a -> WriteTableField) -> Maybe a -> WriteTableField Source #
writeStructTableField :: forall a. IsStruct a => WriteStruct a -> WriteTableField Source #
writeStructTableField' :: Alignment -> InlineSize -> Builder -> WriteTableField Source #
writeUnion :: Word8 -> WriteTable a -> WriteUnion b Source #
writeTable :: [WriteTableField] -> WriteTable a Source #
class WriteVectorElement a where Source #
data WriteVector a Source #
A vector to be written to a flatbuffer.
:: (MonoFoldable mono, Element mono ~ a) | |
=> Int32 |
|
-> mono |
|
-> WriteVector a |
Constructs a flatbuffers vector.
If n
is larger than the length of xs
, this will result in a malformed buffer.
If n
is smaller than the length of xs
, all elements of xs
will still be written to the buffer,
but the client will only be able to read the first n
elements.
Note: fromMonoFoldable
asks for the collection's length to be passed in as an argument rather than use olength
because:
olength
is often O(n), and in some use cases there may be a better way to know the collection's length ahead of time.- Calling
olength
insidefromMonoFoldable
can inhibit some fusions which would otherwise be possible.
Since: 0.2.0.0
Instances
fromMonoFoldable' :: (WriteVectorElement a, MonoFoldable mono, Element mono ~ a) => mono -> WriteVector a Source #
Convenience function, equivalent to:
fromMonoFoldable' xs = fromMonoFoldable (fromIntegral (olength xs)) xs
In some cases it may be slower than using fromMonoFoldable
directly.
Since: 0.2.0.0
fromList :: WriteVectorElement a => Int32 -> [a] -> WriteVector a Source #
fromMonoFoldable
specialized to list
fromList' :: WriteVectorElement a => [a] -> WriteVector a Source #
fromMonoFoldable'
specialized to list
singleton :: WriteVectorElement a => a -> WriteVector a Source #
Creates a flatbuffers vector with a single element
empty :: WriteVectorElement a => WriteVector a Source #
Creates an empty flatbuffers vector
newtype FromFoldable f a Source #
FromFoldable (f a) |
Instances
fromFoldable :: (WriteVectorElement a, Foldable f) => Int32 -> f a -> WriteVector a Source #
fromMonoFoldable
for types that implement Foldable
but not MonoFoldable
.
fromFoldable' :: (WriteVectorElement a, Foldable f) => f a -> WriteVector a Source #
fromMonoFoldable'
for types that implement Foldable
but not MonoFoldable
.
fromByteString :: ByteString -> WriteVector Word8 Source #
Efficiently creates a vector from a ByteString
.
Large ByteString
s are inserted directly, but small ones are copied to ensure that the generated chunks are large on average.
Since: 0.2.0.0
fromLazyByteString :: ByteString -> WriteVector Word8 Source #
Efficiently creates a vector from a lazy ByteString
.
Large chunks of the ByteString
are inserted directly, but small ones are copied to ensure that the generated chunks are large on average.
Since: 0.2.0.0
inlineVector :: (MonoFoldable mono, Element mono ~ a) => (a -> Builder) -> Alignment -> InlineSize -> Int32 -> mono -> WriteTableField Source #
data OffsetInfo Source #
data UnionTableInfo Source #
UnionTableInfo | |
|
:: Alignment | n |
-> Int32 | additionalBytes |
-> BufferSize | |
-> Int32 |
Calculate how much 0-padding is needed so that, after writing additionalBytes
,
the buffer becomes aligned to n
bytes.
Add enough 0-padding so that the buffer becomes aligned to n
after writing additionalBytes
.
utf8length :: Text -> Int32 Source #