Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type ValidationCtx m = (MonadError Text m, MonadReader ValidationState m)
- data ValidationState = ValidationState {}
- modifyContext :: ValidationCtx m => (Ident -> Ident) -> m a -> m a
- data SymbolTable enum struct table union = SymbolTable {}
- type Stage1 = SymbolTable EnumDecl StructDecl TableDecl UnionDecl
- type Stage2 = SymbolTable EnumDecl StructDecl TableDecl UnionDecl
- type Stage3 = SymbolTable EnumDecl StructDecl TableDecl UnionDecl
- type Stage4 = SymbolTable EnumDecl StructDecl TableDecl UnionDecl
- type ValidDecls = SymbolTable EnumDecl StructDecl TableDecl UnionDecl
- createSymbolTables :: FileTree Schema -> FileTree Stage1
- validateSchemas :: MonadError Text m => FileTree Schema -> m (FileTree ValidDecls)
- data RootInfo = RootInfo {
- rootTableNamespace :: !Namespace
- rootTable :: !TableDecl
- rootFileIdent :: !(Maybe Text)
- updateRootTable :: forall m. ValidationCtx m => Schema -> FileTree ValidDecls -> m (FileTree ValidDecls)
- getRootInfo :: forall m. ValidationCtx m => Schema -> FileTree ValidDecls -> m (Maybe RootInfo)
- knownAttributes :: [AttributeDecl]
- idAttr :: Text
- deprecatedAttr :: Text
- requiredAttr :: Text
- forceAlignAttr :: Text
- bitFlagsAttr :: Text
- otherKnownAttributes :: [AttributeDecl]
- data Match enum struct table union
- findDecl :: ValidationCtx m => (HasIdent e, HasIdent s, HasIdent t, HasIdent u) => Namespace -> FileTree (SymbolTable e s t u) -> TypeRef -> m (Match e s t u)
- parentNamespaces :: Namespace -> NonEmpty Namespace
- validateEnums :: forall m. ValidationCtx m => FileTree Stage1 -> m (FileTree Stage2)
- validateEnum :: forall m. ValidationCtx m => (Namespace, EnumDecl) -> m EnumDecl
- data TableFieldWithoutId = TableFieldWithoutId !Ident !TableFieldType !Bool
- validateTables :: ValidationCtx m => FileTree Stage3 -> m (FileTree Stage4)
- validateTable :: forall m. ValidationCtx m => FileTree Stage3 -> (Namespace, TableDecl) -> m TableDecl
- checkNoRequired :: ValidationCtx m => Metadata -> m ()
- checkNoDefault :: ValidationCtx m => Maybe DefaultVal -> m ()
- isRequired :: Metadata -> Required
- validateDefaultValAsInt :: forall m a. (ValidationCtx m, Integral a, Bounded a, Show a) => Maybe DefaultVal -> m (DefaultVal a)
- validateDefaultValAsScientific :: ValidationCtx m => Maybe DefaultVal -> m (DefaultVal Scientific)
- validateDefaultValAsBool :: ValidationCtx m => Maybe DefaultVal -> m (DefaultVal Bool)
- validateDefaultAsEnum :: ValidationCtx m => Maybe DefaultVal -> EnumDecl -> m (DefaultVal Integer)
- validateUnions :: ValidationCtx m => FileTree Stage4 -> m (FileTree ValidDecls)
- validateUnion :: forall m. ValidationCtx m => FileTree Stage4 -> (Namespace, UnionDecl) -> m UnionDecl
- validateStructs :: ValidationCtx m => FileTree Stage2 -> m (FileTree Stage3)
- checkStructCycles :: forall m. ValidationCtx m => FileTree Stage2 -> (Namespace, StructDecl) -> m ()
- data UnpaddedStructField = UnpaddedStructField {}
- validateStruct :: forall m. (MonadState [(Namespace, StructDecl)] m, ValidationCtx m) => FileTree Stage2 -> (Namespace, StructDecl) -> m (Namespace, StructDecl)
- structFieldAlignment :: UnpaddedStructField -> Alignment
- enumAlignment :: EnumType -> Alignment
- enumSize :: EnumType -> Word8
- structFieldTypeSize :: StructFieldType -> InlineSize
- checkDuplicateIdentifiers :: (ValidationCtx m, Foldable f, Functor f, HasIdent a) => f a -> m ()
- checkUndeclaredAttributes :: (ValidationCtx m, HasMetadata a) => a -> m ()
- hasAttribute :: Text -> Metadata -> Bool
- findIntAttr :: ValidationCtx m => Text -> Metadata -> m (Maybe Integer)
- findStringAttr :: ValidationCtx m => Text -> Metadata -> m (Maybe Text)
- throwErrorMsg :: ValidationCtx m => Text -> m a
Documentation
type ValidationCtx m = (MonadError Text m, MonadReader ValidationState m) Source #
data ValidationState Source #
ValidationState | |
|
modifyContext :: ValidationCtx m => (Ident -> Ident) -> m a -> m a Source #
data SymbolTable enum struct table union Source #
Instances
createSymbolTables :: FileTree Schema -> FileTree Stage1 Source #
Takes a collection of schemas, and pairs each type declaration with its corresponding namespace
validateSchemas :: MonadError Text m => FileTree Schema -> m (FileTree ValidDecls) Source #
RootInfo | |
|
updateRootTable :: forall m. ValidationCtx m => Schema -> FileTree ValidDecls -> m (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_type
s.
The root type declaration can point to a table in any schema (root or imported).
getRootInfo :: forall m. ValidationCtx m => Schema -> FileTree ValidDecls -> m (Maybe RootInfo) Source #
requiredAttr :: Text Source #
bitFlagsAttr :: Text Source #
findDecl :: ValidationCtx m => (HasIdent e, HasIdent s, HasIdent t, HasIdent u) => 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. If none is found, the list of namespaces in which the type reference was searched for is returned.
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", ""]
validateEnums :: forall m. ValidationCtx m => FileTree Stage1 -> m (FileTree Stage2) Source #
validateEnum :: forall m. ValidationCtx m => (Namespace, EnumDecl) -> m EnumDecl Source #
validateTables :: ValidationCtx m => FileTree Stage3 -> m (FileTree Stage4) Source #
validateTable :: forall m. ValidationCtx m => FileTree Stage3 -> (Namespace, TableDecl) -> m TableDecl Source #
checkNoRequired :: ValidationCtx m => Metadata -> m () Source #
checkNoDefault :: ValidationCtx m => Maybe DefaultVal -> m () Source #
isRequired :: Metadata -> Required Source #
validateDefaultValAsInt :: forall m a. (ValidationCtx m, Integral a, Bounded a, Show a) => Maybe DefaultVal -> m (DefaultVal a) Source #
validateDefaultValAsScientific :: ValidationCtx m => Maybe DefaultVal -> m (DefaultVal Scientific) Source #
validateDefaultValAsBool :: ValidationCtx m => Maybe DefaultVal -> m (DefaultVal Bool) Source #
validateDefaultAsEnum :: ValidationCtx m => Maybe DefaultVal -> EnumDecl -> m (DefaultVal Integer) Source #
validateUnions :: ValidationCtx m => FileTree Stage4 -> m (FileTree ValidDecls) Source #
validateUnion :: forall m. ValidationCtx m => FileTree Stage4 -> (Namespace, UnionDecl) -> m UnionDecl Source #
validateStructs :: ValidationCtx m => FileTree Stage2 -> m (FileTree Stage3) Source #
checkStructCycles :: forall m. ValidationCtx m => FileTree Stage2 -> (Namespace, StructDecl) -> m () Source #
data UnpaddedStructField Source #
Instances
Eq UnpaddedStructField Source # | |
Defined in FlatBuffers.Internal.Compiler.SemanticAnalysis (==) :: UnpaddedStructField -> UnpaddedStructField -> Bool # (/=) :: UnpaddedStructField -> UnpaddedStructField -> Bool # | |
Show UnpaddedStructField Source # | |
Defined in FlatBuffers.Internal.Compiler.SemanticAnalysis showsPrec :: Int -> UnpaddedStructField -> ShowS # show :: UnpaddedStructField -> String # showList :: [UnpaddedStructField] -> ShowS # |
validateStruct :: forall m. (MonadState [(Namespace, StructDecl)] m, ValidationCtx m) => FileTree Stage2 -> (Namespace, StructDecl) -> m (Namespace, StructDecl) Source #
enumAlignment :: EnumType -> Alignment Source #
enumSize :: EnumType -> Word8 Source #
The size of an enum is either 1, 2, 4 or 8 bytes, so its size fits in a Word8
checkDuplicateIdentifiers :: (ValidationCtx m, Foldable f, Functor f, HasIdent a) => f a -> m () Source #
checkUndeclaredAttributes :: (ValidationCtx m, HasMetadata a) => a -> m () Source #
findIntAttr :: ValidationCtx m => Text -> Metadata -> m (Maybe Integer) Source #
findStringAttr :: ValidationCtx m => Text -> Metadata -> m (Maybe Text) Source #
throwErrorMsg :: ValidationCtx m => Text -> m a Source #