Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- mkFlatBuffers :: FilePath -> Options -> Q [Dec]
- defaultOptions :: Options
- data Options = Options {}
- encode :: WriteTable a -> ByteString
- encodeWithFileIdentifier :: forall a. HasFileIdentifier a => WriteTable a -> ByteString
- none :: WriteUnion a
- decode :: ByteString -> Either ReadError (Table a)
- checkFileIdentifier :: forall a. HasFileIdentifier a => ByteString -> Bool
- data FileIdentifier
- class HasFileIdentifier a where
- data WriteStruct a
- data WriteTable a
- data WriteUnion a
- data Struct a
- data Table a
- data Union a
- = Union !a
- | UnionNone
- | UnionUnknown !Word8
- newtype InlineSize = InlineSize {}
- newtype Alignment = Alignment {
- unAlignment :: Word8
- class IsStruct a where
- type ReadError = String
TemplateHaskell
mkFlatBuffers :: FilePath -> Options -> Q [Dec] Source #
Generates constructors and accessors for all data types declared in the given flatbuffers schema whose namespace matches the current module.
namespace Data.Game; table Monster {}
{-# LANGUAGE TemplateHaskell #-} module Data.Game where import FlatBuffers $(mkFlatBuffers "schemas/game.fbs" defaultOptions)
defaultOptions :: Options Source #
Default flatbuffers options:
Options { includeDirectories = [] , compileAllSchemas = False }
Options to control how/which flatbuffers constructors/accessor should be generated.
Options can be set using record syntax on defaultOptions
with the fields below.
defaultOptions { compileAllSchemas = True }
Options | |
|
Creating a flatbuffer
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.
none :: WriteUnion a Source #
Constructs a missing union table field / vector element.
Reading a flatbuffer
decode :: ByteString -> Either ReadError (Table a) Source #
Deserializes a flatbuffer from a lazy ByteString
.
checkFileIdentifier :: forall a. HasFileIdentifier a => ByteString -> Bool Source #
Checks if a buffer contains the file identifier for a root table a
, to see if it's
safe to decode it to a Table
.
It should be used in conjunction with -XTypeApplications
.
{-# LANGUAGE TypeApplications #-} if checkFileIdentifier @Monster bs then decode @Monster bs else return someMonster
File Identifier
data FileIdentifier Source #
An identifier that's used to "mark" a buffer.
To add this marker to a buffer, use encodeWithFileIdentifier
.
To check whether a buffer contains the marker before decoding it, use checkFileIdentifier
.
For more information on file identifiers, see :
- The library's docs
- Section "File identification and extension" of the official docs
Instances
Eq FileIdentifier Source # | |
Defined in FlatBuffers.Internal.FileIdentifier (==) :: FileIdentifier -> FileIdentifier -> Bool # (/=) :: FileIdentifier -> FileIdentifier -> Bool # | |
Show FileIdentifier Source # | |
Defined in FlatBuffers.Internal.FileIdentifier showsPrec :: Int -> FileIdentifier -> ShowS # show :: FileIdentifier -> String # showList :: [FileIdentifier] -> ShowS # |
class HasFileIdentifier a where Source #
Associates a type with a file identifier.
To create an association, declare a root_type
and file_identifier
in your schema.
table Player {} root_type Player; file_identifier "PLYR";
Types
data 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) :: Type Source # fromFoldable :: Foldable f => Int32 -> f (WriteStruct a) -> WriteVector (WriteStruct a) Source # | |
newtype WriteVector (WriteStruct a) Source # | |
Defined in FlatBuffers.Internal.Write |
data 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) :: Type Source # fromFoldable :: Foldable f => Int32 -> f (WriteTable a) -> 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.
Instances
WriteVectorElement (WriteUnion a) Source # | |
Defined in FlatBuffers.Internal.Write data WriteVector (WriteUnion a) :: Type Source # fromFoldable :: Foldable f => Int32 -> f (WriteUnion a) -> WriteVector (WriteUnion a) Source # | |
data WriteVector (WriteUnion a) Source # | |
Defined in FlatBuffers.Internal.Write |
A struct that is being read from a flatbuffer.
Instances
VectorElement (Struct a) Source # | |
Defined in FlatBuffers.Internal.Read | |
data Vector (Struct a) Source # | |
Defined in FlatBuffers.Internal.Read |
A table that is being read from a flatbuffer.
Instances
VectorElement (Table a) Source # | |
Defined in FlatBuffers.Internal.Read | |
HasPosition (Vector (Table a)) Source # | |
newtype Vector (Table a) Source # | |
Defined in FlatBuffers.Internal.Read |
A union that is being read from a flatbuffer.
Instances
VectorElement (Union a) Source # | |
Defined in FlatBuffers.Internal.Read | |
data Vector (Union a) Source # | |
Defined in FlatBuffers.Internal.Read data Vector (Union a) = VectorUnion {
|
newtype InlineSize Source #
The number of bytes occupied by a piece of data that's stored "inline"
"inline" here means "stored directly in a table or a vector, and not by reference". E.g.: numeric types, booleans, structs, offsets.
Instances
The memory alignment (in bytes) for a piece of data in a flatbuffer.
E.g., Int32
are always aligned to 4 bytes.
This number should always be a power of 2 in the range [1, 16].
Instances
Bounded Alignment Source # | |
Enum Alignment Source # | |
Defined in FlatBuffers.Internal.Types succ :: Alignment -> Alignment # pred :: Alignment -> Alignment # fromEnum :: Alignment -> Int # enumFrom :: Alignment -> [Alignment] # enumFromThen :: Alignment -> Alignment -> [Alignment] # enumFromTo :: Alignment -> Alignment -> [Alignment] # enumFromThenTo :: Alignment -> Alignment -> Alignment -> [Alignment] # | |
Eq Alignment Source # | |
Integral Alignment Source # | |
Defined in FlatBuffers.Internal.Types | |
Num Alignment Source # | |
Defined in FlatBuffers.Internal.Types | |
Ord Alignment Source # | |
Defined in FlatBuffers.Internal.Types | |
Real Alignment Source # | |
Defined in FlatBuffers.Internal.Types toRational :: Alignment -> Rational # | |
Show Alignment Source # | |