flatbuffers-0.3.0.0: Haskell implementation of the FlatBuffers protocol.
Safe HaskellNone
LanguageHaskell2010

FlatBuffers.Internal.Compiler.SemanticAnalysis

Synopsis

Documentation

newtype Validation a Source #

A monad that allows short-circuiting when a validation error is found.

It keeps track of which item is currently being validated, so that when an error happens, we can show the user a better error message with contextual information.

data ValidationState Source #

Constructors

ValidationState 

Fields

class Monad m => MonadValidation m where Source #

Methods

validating :: HasIdent a => a -> m b -> m b Source #

Start validating an item a

resetContext :: m a -> m a Source #

Clear validation context, i.e. forget which item is currently being validated, if any.

getContext :: m [Ident] Source #

Get the path to the item currently being validated

getDeclaredAttributes :: m (Set AttributeDecl) Source #

Get a list of all the attributes declared in every loaded schema

throwErrorMsg :: String -> m a Source #

Fail validation with a message

data SymbolTable enum struct table union Source #

Constructors

SymbolTable 

Fields

Instances

Instances details
(Eq enum, Eq struct, Eq table, Eq union) => Eq (SymbolTable enum struct table union) Source # 
Instance details

Defined in FlatBuffers.Internal.Compiler.SemanticAnalysis

Methods

(==) :: SymbolTable enum struct table union -> SymbolTable enum struct table union -> Bool #

(/=) :: SymbolTable enum struct table union -> SymbolTable enum struct table union -> Bool #

(Show enum, Show struct, Show table, Show union) => Show (SymbolTable enum struct table union) Source # 
Instance details

Defined in FlatBuffers.Internal.Compiler.SemanticAnalysis

Methods

showsPrec :: Int -> SymbolTable enum struct table union -> ShowS #

show :: SymbolTable enum struct table union -> String #

showList :: [SymbolTable enum struct table union] -> ShowS #

Semigroup (SymbolTable e s t u) Source # 
Instance details

Defined in FlatBuffers.Internal.Compiler.SemanticAnalysis

Methods

(<>) :: SymbolTable e s t u -> SymbolTable e s t u -> SymbolTable e s t u #

sconcat :: NonEmpty (SymbolTable e s t u) -> SymbolTable e s t u #

stimes :: Integral b => b -> SymbolTable e s t u -> SymbolTable e s t u #

Monoid (SymbolTable e s t u) Source # 
Instance details

Defined in FlatBuffers.Internal.Compiler.SemanticAnalysis

Methods

mempty :: SymbolTable e s t u #

mappend :: SymbolTable e s t u -> SymbolTable e s t u -> SymbolTable e s t u #

mconcat :: [SymbolTable e s t u] -> SymbolTable e s t u #

createSymbolTables :: FileTree Schema -> Validation (FileTree Stage1) Source #

Takes a collection of schemas, and pairs each type declaration with its corresponding namespace

insertSymbol :: HasIdent a => Namespace -> a -> Map (Namespace, Ident) a -> Validation (Map (Namespace, Ident) a) Source #

Fails if the key is already present in the map.

updateRootTable :: Schema -> FileTree ValidDecls -> Validation (FileTree ValidDecls) Source #

Finds the root table (if any) and sets the tableIsRoot flag accordingly. We only care about root_type declarations in the root schema. Imported schemas are not scanned for root_types. The root type declaration can point to a table in any schema (root or imported).

getRootInfo :: Schema -> FileTree ValidDecls -> Validation (Maybe RootInfo) Source #

Finds the root_type declaration (if any), and what table it's pointing to.

data Match enum struct table union Source #

Constructors

MatchE !Namespace !enum 
MatchS !Namespace !struct 
MatchT !Namespace !table 
MatchU !Namespace !union 

findDecl :: MonadValidation m => Namespace -> FileTree (SymbolTable e s t u) -> TypeRef -> m (Match e s t u) Source #

Looks for a type reference in a set of type declarations.

parentNamespaces :: Namespace -> NonEmpty Namespace Source #

Returns a list of all the namespaces "between" the current namespace and the root namespace, in that order. See: https://github.com/google/flatbuffers/issues/5234#issuecomment-471680403

parentNamespaces "A.B.C" == ["A.B.C", "A.B", "A", ""]

type ValidatedStructs = Map (Namespace, Ident) StructDecl Source #

Cache of already validated structs.

When we're validating a struct A, it may contain an inner struct B which also needs validating. B needs to be fully validated before we can consider A valid.

If we've validated B in a previous iteration, we will find it in this Map and therefore avoid re-validating it.

enumSize :: EnumType -> Word8 Source #

The size of an enum is either 1, 2, 4 or 8 bytes, so its size fits in a Word8

isPowerOfTwo :: (Num a, Bits a) => a -> Bool Source #