Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- (~>) :: Type -> Type -> Type
- data Options = Options {}
- defaultOptions :: Options
- mkFlatBuffers :: FilePath -> Options -> Q [Dec]
- compileSymbolTable :: ValidDecls -> Q [Dec]
- mkEnum :: (Namespace, EnumDecl) -> Q [Dec]
- mkEnumDataDec :: Name -> NonEmpty Name -> Dec
- mkToEnum :: Name -> EnumDecl -> NonEmpty (EnumVal, Name) -> Q [Dec]
- mkFromEnum :: Name -> EnumDecl -> NonEmpty (EnumVal, Name) -> Q [Dec]
- mkStruct :: (Namespace, StructDecl) -> Q [Dec]
- mkIsStructInstance :: Name -> StructDecl -> Q [Dec]
- mkStructConstructor :: Name -> StructDecl -> Q (Dec, Dec)
- mkStructConstructorArg :: StructField -> Q (Type, Pat, NonEmpty Exp)
- mkStructFieldGetter :: Name -> StructDecl -> StructField -> [Dec]
- mkTable :: (Namespace, TableDecl) -> Q [Dec]
- mkTableFileIdentifier :: Name -> IsRoot -> [Dec]
- mkTableConstructor :: Name -> TableDecl -> Q (Dec, Dec)
- mkTableContructorArg :: TableField -> Q ([Type], [Pat], [Exp])
- mkTableFieldGetter :: Name -> TableDecl -> TableField -> [Dec]
- mkUnion :: (Namespace, UnionDecl) -> Q [Dec]
- mkUnionDataDec :: Name -> NonEmpty (UnionVal, Name) -> Dec
- mkUnionConstructors :: Name -> UnionDecl -> Q [Dec]
- mkReadUnionFun :: Name -> NonEmpty Name -> UnionDecl -> Q [Dec]
- enumTypeToType :: EnumType -> Type
- enumTypeToTableFieldType :: Integral a => EnumType -> DefaultVal a -> TableFieldType
- enumTypeToStructFieldType :: EnumType -> StructFieldType
- enumTypeToVectorElementType :: EnumType -> VectorElementType
- structFieldTypeToWriteType :: StructFieldType -> Type
- structFieldTypeToReadType :: StructFieldType -> Type
- tableFieldTypeToWriteType :: TableFieldType -> Type
- tableFieldTypeToReadType :: TableFieldType -> Type
- vectorElementTypeToWriteType :: VectorElementType -> Type
- vectorElementTypeToReadType :: VectorElementType -> Type
- typeRefToType :: TypeRef -> Type
- requiredType :: Required -> Type -> Type
- mkName' :: Text -> Name
- newName' :: Text -> Q Name
- intLitP :: Integral i => i -> Pat
- intLitE :: Integral i => i -> Exp
- realLitE :: Real i => i -> Exp
- textLitE :: Text -> Exp
- stringLitE :: Text -> Exp
- app :: [Exp] -> Exp
- compose :: [Exp] -> Exp
Documentation
(~>) :: Type -> Type -> Type infixr 1 Source #
Helper method to create function types.
ConT ''Int ~> ConT ''String === Int -> String
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 | |
|
defaultOptions :: Options Source #
Default flatbuffers options:
Options { includeDirectories = [] , compileAllSchemas = False }
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)
compileSymbolTable :: ValidDecls -> Q [Dec] Source #
mkIsStructInstance :: Name -> StructDecl -> Q [Dec] Source #
mkStructConstructor :: Name -> StructDecl -> Q (Dec, Dec) Source #
mkStructConstructorArg :: StructField -> Q (Type, Pat, NonEmpty Exp) Source #
mkStructFieldGetter :: Name -> StructDecl -> StructField -> [Dec] Source #
mkTableContructorArg :: TableField -> Q ([Type], [Pat], [Exp]) Source #
mkTableFieldGetter :: Name -> TableDecl -> TableField -> [Dec] Source #
enumTypeToType :: EnumType -> Type Source #
enumTypeToTableFieldType :: Integral a => EnumType -> DefaultVal a -> TableFieldType Source #
typeRefToType :: TypeRef -> Type Source #
stringLitE :: Text -> Exp Source #
Applies a function to multiple arguments. Assumes the list is not empty.