flatbuffers: Haskell implementation of the FlatBuffers protocol.

[ bsd3, data, library, network, serialization ] [ Propose Tags ]
Versions [RSS] 0.1.0.0, 0.2.0.0, 0.3.0.0, 0.4.0.0
Dependencies base (>=4.11 && <5), binary (>=0.8.4.0), bytestring (>=0.10.8.0), containers (>=0.5.11.0), directory (>=1.3.1.2), filepath (>=1.4.2), megaparsec (>=7.0), mtl (>=2.2.1), parser-combinators (>=1.0), scientific (>=0.3.5.2), template-haskell (>=2.13.0.0 && <2.18.0.0), text (>=1.2.3.0 && <2.0), text-manipulate (>=0.1.0) [details]
License BSD-3-Clause
Copyright 2019 Diogo Castro
Author Diogo Castro
Maintainer dc@diogocastro.com
Revised Revision 1 made by dcastro at 2024-02-06T14:46:12Z
Category Data, Serialization, Network
Home page https://github.com/dcastro/haskell-flatbuffers
Bug tracker https://github.com/dcastro/haskell-flatbuffers/issues
Source repo head: git clone https://github.com/dcastro/haskell-flatbuffers
Uploaded by dcastro at 2019-09-22T11:24:59Z
Distributions
Downloads 1700 total (14 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2019-09-22 [all 1 reports]

Readme for flatbuffers-0.1.0.0

[back to package description]

Haskell Flatbuffers

An implementation of the flatbuffers protocol in Haskell.

Build Status Hackage

Getting started

  1. Start off by writing a flatbuffers schema with the data structures you want to serialize/deserialize.
    namespace Data.Game;
    
    table Monster {
      name: string;
      hp: int;
      locations: [string] (required);
    }
    
  2. Create a Haskell module named after the namespace in the schema.
    module Data.Game where
    
  3. Use mkFlatBuffers to generate constructors and accessors for the data types in your schema.
    {-# LANGUAGE TemplateHaskell #-}
    
    module Data.Game where
    import FlatBuffers
    
    $(mkFlatBuffers "schemas/game.fbs" defaultOptions)
    
  4. The following declarations will be generated for you.
    data Monster
    
    -- Constructor
    monster :: Maybe Text -> Maybe Int32 -> WriteVector Text -> WriteTable Monster
    
    -- Accessors
    monsterName      :: Table Monster -> Either ReadError (Maybe Text)
    monsterHp        :: Table Monster -> Either ReadError Int32
    monsterLocations :: Table Monster -> Either ReadError (Vector Text)
    

We can now construct a flatbuffer using encode and read it using decode:

{-# LANGUAGE OverloadedStrings #-}

import           FlatBuffers
import qualified FlatBuffers.Vector as Vector

-- Writing
let byteString = encode $
      monster
        (Just "Poring")
        (Just 50)
        (Vector.fromList 2 ["Prontera Field", "Payon Forest"])

-- Reading
do
  someMonster <- decode byteString
  name        <- monsterName someMonster
  hp          <- monsterHp someMonster
  locations   <- monsterLocations someMonster >>= Vector.toList
  Right ("Monster: " <> show name <> " (" <> show hp <> " HP) can be found in " <> show locations)

For more info on code generation and examples, see codegen.

Enums

enum Color: short { Red, Green, Blue }

Given the enum declarationa above, the following code will be generated:

data Color
  = ColorRed
  | ColorGreen
  | ColorBlue
  deriving (Eq, Show, Read, Ord, Bounded)

toColor   :: Int16 -> Maybe Color
fromColor :: Color -> Int16

Usage:

table Monster {
  color: Color;
}
data Monster

monster      :: Maybe Int16 -> WriteTable Monster
monsterColor :: Table Monster -> Either ReadError Int16

-- Writing
let byteString = encode $
      monster (Just (fromColor ColorBlue))

-- Reading
do
  someMonster <- decode byteString
  short       <- monsterColor someMonster
  case toColor short of
    Just ColorRed   -> Right "This monster is red"
    Just ColorGreen -> Right "This monster is green"
    Just ColorBlue  -> Right "This monster is blue"
    Nothing         -> Left ("Unknown color: " <> show short) -- Forwards compatibility

Structs

struct Coord {
  x: long;
  y: long;
}

Given the struct declaration above, the following code will be generated:

data Coord
instance IsStruct Coord

--  Constructor
coord :: Int64 -> Int64 -> WriteStruct Coord

-- Accessors
coordX :: Struct Coord -> Either ReadError Int64
coordY :: Struct Coord -> Either ReadError Int64

Usage:

table Monster {
  position: Coord (required);
}
data Monster

monster         :: WriteStruct Coord -> WriteTable Monster
monsterPosition :: Table Monster -> Either ReadError (Struct Coord)

-- Writing
let byteString = encode $
      monster (coord 123 456)

-- Reading
do
  someMonster <- decode byteString
  pos         <- monsterPosition someMonster
  x           <- coordX pos
  y           <- coordY pos
  Right ("Monster is located at " <> show x <> ", " <> show y)

Unions

table Sword { power: int; }
table Axe { power: int; }
union Weapon { Sword, Axe }

Given the union declaration above, the following code will be generated:

-- Accessors
data Weapon
  = WeaponSword !(Table Sword)
  | WeaponAxe   !(Table Axe)

-- Constructors
weaponSword :: WriteTable Sword -> WriteUnion Weapon
weaponAxe   :: WriteTable Axe   -> WriteUnion Weapon

Usage:

table Character {
  weapon: Weapon;
}
data Character

character       :: WriteUnion Weapon -> WriteTable Character
characterWeapon :: Table Character -> Either ReadError (Union Weapon)

-- Writing
let byteString = encode $
      character
        (weaponSword (sword (Just 1000)))

-- Reading
do
  someCharacter <- decode byteString
  weapon        <- characterWeapon someCharacter
  case weapon of
    Union (WeaponSword sword) -> do
      power <- swordPower sword
      Right ("Weilding a sword with " <> show power <> " Power.")
    Union (WeaponAxe axe) -> do
      power <- axePower axe
      Right ("Weilding an axe with " <> show power <> " Power.")
    UnionNone         -> Right "Character has no weapon"
    UnionUnknown byte -> Left "Unknown weapon" -- Forwards compatibility

Note that, like in the official FlatBuffers implementation, unions are always optional. Adding the required attribute to a union field has no effect.

To create a character with no weapon, use none :: WriteUnion a

let byteString = encode $
      character none

File Identifiers

From "File identification and extension":

Typically, a FlatBuffer binary buffer is not self-describing, i.e. it needs you to know its schema to parse it correctly. But if you want to use a FlatBuffer as a file format, it would be convenient to be able to have a "magic number" in there, like most file formats have, to be able to do a sanity check to see if you're reading the kind of file you're expecting.

Now, you can always prefix a FlatBuffer with your own file header, but FlatBuffers has a built-in way to add an identifier to a FlatBuffer that takes up minimal space, and keeps the buffer compatible with buffers that don't have such an identifier.

table Monster { name: string; }

root_type Monster;
file_identifier "MONS";
data Monster
instance HasFileIdentifier Monster

-- Usual constructor and accessors...

We can now construct a flatbuffer using encodeWithFileIdentifier and use checkFileIdentifier to check if it's safe to decode it to a specific type:

{-# LANGUAGE TypeApplications #-}

-- Writing
let byteString = encodeWithFileIdentifier $
      monster (Just "Poring")

-- Reading
if checkFileIdentifier @Monster byteString then do
  someMonster <- decode byteString
  monsterName someMonster
else if checkFileIdentifier @Character byteString then do
  someCharacter <- decode byteString
  characterName someCharacter
else
  Left "Unexpected flatbuffer identifier"

Codegen

You can check exactly which declarations were generated by browsing your module in ghci:

λ> :m Data.Game FlatBuffers FlatBuffers.Vector
λ> :browse Data.Game
data Monster
monster :: Maybe Int32 -> WriteTable Monster
monsterHp :: Table Monster -> Either ReadError Int32

Or by launching a local hoogle server with Stack:

> stack hoogle --rebuild --server

There are lots of examples in the test/Examples folder and the THSpec module.

In particular, test/Examples/schema.fbs and test/Examples/vector_of_unions.fbs contain a variety of data structures and Examples.HandWritten demonstrates what the code generated by mkFlatBuffers would look like.

TODO

Features

Other

  • TH: sort table fields by size + support original_order attribute
  • Add support for storing unboxed vectors, which do not have a Foldable instance. Maybe use MonoFoldable from the mono-traversable package
  • Enrich Vector API: drop, take, null, folds, sum, elem, for_, traverse_, ideally support most of operations in Data.Foldable
  • Add MonoFoldable (Vector a) instance
  • Improve error messages during SemanticAnalysis stage, provide source code location
  • Try alternative bytestring builders: fast-builder, blaze-builder
  • Try alternative bytestring parsers: cereal
  • Better support for enums