flatbuffers-0.2.0.0: Haskell implementation of the FlatBuffers protocol.

Safe HaskellNone
LanguageHaskell2010

FlatBuffers.Internal.Write

Synopsis

Documentation

type Position = Int32 Source #

The position of something in a buffer, expressed as the number of bytes counting from the end.

newtype WriteStruct a Source #

A struct to be written to a flatbuffer.

Constructors

WriteStruct 

Fields

newtype WriteTable a Source #

A table to be written to a flatbuffer.

Instances
WriteVectorElement (WriteTable a) Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector (WriteTable a) :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ WriteTable a) => Int32 -> mono -> WriteVector (WriteTable a) Source #

newtype WriteVector (WriteTable a) Source # 
Instance details

Defined in FlatBuffers.Internal.Write

data WriteUnion a Source #

A union to be written to a flatbuffer.

Constructors

Some !Word8 !(State FBState Position) 
None 

encode :: WriteTable a -> ByteString Source #

Serializes a flatbuffer table as a lazy ByteString.

encodeWithFileIdentifier :: forall a. HasFileIdentifier a => WriteTable a -> ByteString Source #

Serializes a flatbuffer table as a lazy ByteString and adds a File Identifier.

write :: Int32 -> Builder -> FBState -> FBState Source #

Writes something (unaligned) to the buffer.

writeInt32 :: Int32 -> FBState -> FBState Source #

Writes a 32-bit int (unaligned) to the buffer.

none :: WriteUnion a Source #

Constructs a missing union table field / vector element.

class WriteVectorElement a where Source #

Associated Types

data WriteVector a Source #

A vector to be written to a flatbuffer.

Methods

fromMonoFoldable Source #

Arguments

:: (MonoFoldable mono, Element mono ~ a) 
=> Int32

n: the number of elements in xs

-> mono

xs: a collection

-> 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:

  1. 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.
  2. Calling olength inside fromMonoFoldable can inhibit some fusions which would otherwise be possible.

Since: 0.2.0.0

Instances
WriteVectorElement Bool Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector Bool :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ Bool) => Int32 -> mono -> WriteVector Bool Source #

WriteVectorElement Double Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector Double :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ Double) => Int32 -> mono -> WriteVector Double Source #

WriteVectorElement Float Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector Float :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ Float) => Int32 -> mono -> WriteVector Float Source #

WriteVectorElement Int8 Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector Int8 :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ Int8) => Int32 -> mono -> WriteVector Int8 Source #

WriteVectorElement Int16 Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector Int16 :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ Int16) => Int32 -> mono -> WriteVector Int16 Source #

WriteVectorElement Int32 Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector Int32 :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ Int32) => Int32 -> mono -> WriteVector Int32 Source #

WriteVectorElement Int64 Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector Int64 :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ Int64) => Int32 -> mono -> WriteVector Int64 Source #

WriteVectorElement Word8 Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector Word8 :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ Word8) => Int32 -> mono -> WriteVector Word8 Source #

WriteVectorElement Word16 Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector Word16 :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ Word16) => Int32 -> mono -> WriteVector Word16 Source #

WriteVectorElement Word32 Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector Word32 :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ Word32) => Int32 -> mono -> WriteVector Word32 Source #

WriteVectorElement Word64 Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector Word64 :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ Word64) => Int32 -> mono -> WriteVector Word64 Source #

WriteVectorElement Text Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector Text :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ Text) => Int32 -> mono -> WriteVector Text Source #

WriteVectorElement (WriteUnion a) Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector (WriteUnion a) :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ WriteUnion a) => Int32 -> mono -> WriteVector (WriteUnion a) Source #

WriteVectorElement (WriteTable a) Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector (WriteTable a) :: Type Source #

Methods

fromMonoFoldable :: (MonoFoldable mono, Element mono ~ WriteTable a) => Int32 -> mono -> WriteVector (WriteTable a) Source #

IsStruct a => WriteVectorElement (WriteStruct a) Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Associated Types

data WriteVector (WriteStruct a) :: Type Source #

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

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 #

Constructors

FromFoldable (f a) 
Instances
Foldable f => Foldable (FromFoldable f) Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Methods

fold :: Monoid m => FromFoldable f m -> m #

foldMap :: Monoid m => (a -> m) -> FromFoldable f a -> m #

foldr :: (a -> b -> b) -> b -> FromFoldable f a -> b #

foldr' :: (a -> b -> b) -> b -> FromFoldable f a -> b #

foldl :: (b -> a -> b) -> b -> FromFoldable f a -> b #

foldl' :: (b -> a -> b) -> b -> FromFoldable f a -> b #

foldr1 :: (a -> a -> a) -> FromFoldable f a -> a #

foldl1 :: (a -> a -> a) -> FromFoldable f a -> a #

toList :: FromFoldable f a -> [a] #

null :: FromFoldable f a -> Bool #

length :: FromFoldable f a -> Int #

elem :: Eq a => a -> FromFoldable f a -> Bool #

maximum :: Ord a => FromFoldable f a -> a #

minimum :: Ord a => FromFoldable f a -> a #

sum :: Num a => FromFoldable f a -> a #

product :: Num a => FromFoldable f a -> a #

Foldable f => MonoFoldable (FromFoldable f a) Source # 
Instance details

Defined in FlatBuffers.Internal.Write

Methods

ofoldMap :: Monoid m => (Element (FromFoldable f a) -> m) -> FromFoldable f a -> m #

ofoldr :: (Element (FromFoldable f a) -> b -> b) -> b -> FromFoldable f a -> b #

ofoldl' :: (a0 -> Element (FromFoldable f a) -> a0) -> a0 -> FromFoldable f a -> a0 #

otoList :: FromFoldable f a -> [Element (FromFoldable f a)] #

oall :: (Element (FromFoldable f a) -> Bool) -> FromFoldable f a -> Bool #

oany :: (Element (FromFoldable f a) -> Bool) -> FromFoldable f a -> Bool #

onull :: FromFoldable f a -> Bool #

olength :: FromFoldable f a -> Int #

olength64 :: FromFoldable f a -> Int64 #

ocompareLength :: Integral i => FromFoldable f a -> i -> Ordering #

otraverse_ :: Applicative f0 => (Element (FromFoldable f a) -> f0 b) -> FromFoldable f a -> f0 () #

ofor_ :: Applicative f0 => FromFoldable f a -> (Element (FromFoldable f a) -> f0 b) -> f0 () #

omapM_ :: Applicative m => (Element (FromFoldable f a) -> m ()) -> FromFoldable f a -> m () #

oforM_ :: Applicative m => FromFoldable f a -> (Element (FromFoldable f a) -> m ()) -> m () #

ofoldlM :: Monad m => (a0 -> Element (FromFoldable f a) -> m a0) -> a0 -> FromFoldable f a -> m a0 #

ofoldMap1Ex :: Semigroup m => (Element (FromFoldable f a) -> m) -> FromFoldable f a -> m #

ofoldr1Ex :: (Element (FromFoldable f a) -> Element (FromFoldable f a) -> Element (FromFoldable f a)) -> FromFoldable f a -> Element (FromFoldable f a) #

ofoldl1Ex' :: (Element (FromFoldable f a) -> Element (FromFoldable f a) -> Element (FromFoldable f a)) -> FromFoldable f a -> Element (FromFoldable f a) #

headEx :: FromFoldable f a -> Element (FromFoldable f a) #

lastEx :: FromFoldable f a -> Element (FromFoldable f a) #

unsafeHead :: FromFoldable f a -> Element (FromFoldable f a) #

unsafeLast :: FromFoldable f a -> Element (FromFoldable f a) #

maximumByEx :: (Element (FromFoldable f a) -> Element (FromFoldable f a) -> Ordering) -> FromFoldable f a -> Element (FromFoldable f a) #

minimumByEx :: (Element (FromFoldable f a) -> Element (FromFoldable f a) -> Ordering) -> FromFoldable f a -> Element (FromFoldable f a) #

oelem :: Element (FromFoldable f a) -> FromFoldable f a -> Bool #

onotElem :: Element (FromFoldable f a) -> FromFoldable f a -> Bool #

type Element (FromFoldable f a) Source # 
Instance details

Defined in FlatBuffers.Internal.Write

type Element (FromFoldable f a) = a

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 ByteStrings 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 TextInfo Source #

Constructors

TextInfo 

data OffsetInfo Source #

Constructors

OffsetInfo 

Fields

data TableInfo Source #

Constructors

TableInfo 

data Vecs a Source #

Constructors

Vecs ![Word8] ![Maybe (State FBState Position)] 

calcPadding Source #

Arguments

:: 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.

alignTo Source #

Arguments

:: Alignment

n

-> Int32

additionalBytes

-> FBState 
-> FBState 

Add enough 0-padding so that the buffer becomes aligned to n after writing additionalBytes.