flatbuffers-0.2.0.0: Haskell implementation of the FlatBuffers protocol.

Safe HaskellNone
LanguageHaskell2010

FlatBuffers

Contents

Synopsis

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
  }

data Options Source #

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 }

Constructors

Options 

Fields

  • includeDirectories :: [FilePath]

    Directories to search for includes (same as flatc -I option).

  • compileAllSchemas :: Bool

    Generate code not just for the root schema, but for all schemas it includes as well (same as flatc --gen-all option).

Instances
Eq Options Source # 
Instance details

Defined in FlatBuffers.Internal.Compiler.TH

Methods

(==) :: Options -> Options -> Bool #

(/=) :: Options -> Options -> Bool #

Show Options Source # 
Instance details

Defined in FlatBuffers.Internal.Compiler.TH

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 :

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.

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

data Struct a Source #

A struct that is being read from a flatbuffer.

Instances
IsStruct a => VectorElement (Struct a) Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector (Struct a) :: Type Source #

data Vector (Struct a) Source # 
Instance details

Defined in FlatBuffers.Internal.Read

data Table a Source #

A table that is being read from a flatbuffer.

Instances
VectorElement (Table a) Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector (Table a) :: Type Source #

data Vector (Table a) Source # 
Instance details

Defined in FlatBuffers.Internal.Read

data Union a Source #

A union that is being read from a flatbuffer.

Constructors

Union !a 
UnionNone 
UnionUnknown !Word8 

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.

Constructors

InlineSize 

Fields

Instances
Bounded InlineSize Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Enum InlineSize Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Eq InlineSize Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Integral InlineSize Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Num InlineSize Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Ord InlineSize Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Real InlineSize Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Show InlineSize Source # 
Instance details

Defined in FlatBuffers.Internal.Types

newtype Alignment Source #

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

Constructors

Alignment 

Fields

Instances
Bounded Alignment Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Enum Alignment Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Eq Alignment Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Integral Alignment Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Num Alignment Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Ord Alignment Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Real Alignment Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Show Alignment Source # 
Instance details

Defined in FlatBuffers.Internal.Types

Display Alignment Source # 
Instance details

Defined in FlatBuffers.Internal.Types

class IsStruct a where Source #

Metadata for a struct type.