Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Validation a = Validation {}
- data ValidationState = ValidationState {}
- class Monad m => MonadValidation m where
- validating :: HasIdent a => a -> m b -> m b
- resetContext :: m a -> m a
- getContext :: m [Ident]
- getDeclaredAttributes :: m (Set AttributeDecl)
- throwErrorMsg :: String -> 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
- validateSchemas :: FileTree Schema -> Either String (FileTree ValidDecls)
- createSymbolTables :: FileTree Schema -> Validation (FileTree Stage1)
- insertSymbol :: HasIdent a => Namespace -> a -> Map (Namespace, Ident) a -> Validation (Map (Namespace, Ident) a)
- data RootInfo = RootInfo {
- rootTableNamespace :: !Namespace
- rootTable :: !TableDecl
- rootFileIdent :: !(Maybe Text)
- updateRootTable :: Schema -> FileTree ValidDecls -> Validation (FileTree ValidDecls)
- getRootInfo :: Schema -> FileTree ValidDecls -> Validation (Maybe RootInfo)
- knownAttributes :: [AttributeDecl]
- idAttr :: Text
- deprecatedAttr :: Text
- requiredAttr :: Text
- forceAlignAttr :: Text
- bitFlagsAttr :: Text
- otherKnownAttributes :: [AttributeDecl]
- data Match enum struct table union
- findDecl :: MonadValidation m => Namespace -> FileTree (SymbolTable e s t u) -> TypeRef -> m (Match e s t u)
- parentNamespaces :: Namespace -> NonEmpty Namespace
- validateEnums :: FileTree Stage1 -> Validation (FileTree Stage2)
- validateEnum :: (Namespace, Ident) -> EnumDecl -> Validation EnumDecl
- data TableFieldWithoutId = TableFieldWithoutId !Ident !TableFieldType !Bool
- validateTables :: FileTree Stage3 -> Validation (FileTree Stage4)
- validateTable :: FileTree Stage3 -> (Namespace, Ident) -> TableDecl -> Validation TableDecl
- checkNoRequired :: Metadata -> Validation ()
- checkNoDefault :: Maybe DefaultVal -> Validation ()
- isRequired :: Metadata -> Required
- validateDefaultValAsInt :: forall a. (Integral a, Bounded a, Display a) => Maybe DefaultVal -> Validation (DefaultVal Integer)
- validateDefaultValAsScientific :: Maybe DefaultVal -> Validation (DefaultVal Scientific)
- validateDefaultValAsBool :: Maybe DefaultVal -> Validation (DefaultVal Bool)
- validateDefaultAsEnum :: Maybe DefaultVal -> EnumDecl -> Validation (DefaultVal Integer)
- scientificToInteger :: forall a. (Integral a, Bounded a, Display a) => Scientific -> String -> Validation (DefaultVal Integer)
- validateUnions :: FileTree Stage4 -> Validation (FileTree ValidDecls)
- validateUnion :: FileTree Stage4 -> (Namespace, Ident) -> UnionDecl -> Validation UnionDecl
- type ValidatedStructs = Map (Namespace, Ident) StructDecl
- validateStructs :: FileTree Stage2 -> Validation (FileTree Stage3)
- checkStructCycles :: forall m. MonadValidation m => FileTree Stage2 -> (Namespace, StructDecl) -> m ()
- data UnpaddedStructField = UnpaddedStructField {}
- validateStruct :: forall m. (MonadState ValidatedStructs m, MonadValidation m) => FileTree Stage2 -> Namespace -> StructDecl -> m StructDecl
- structFieldAlignment :: UnpaddedStructField -> Alignment
- enumAlignment :: EnumType -> Alignment
- enumSize :: EnumType -> Word8
- structFieldTypeSize :: StructFieldType -> InlineSize
- checkDuplicateIdentifiers :: (MonadValidation m, Foldable f, Functor f, HasIdent a) => f a -> m ()
- checkUndeclaredAttributes :: (MonadValidation m, HasMetadata a) => a -> m ()
- hasAttribute :: Text -> Metadata -> Bool
- findIntAttr :: MonadValidation m => Text -> Metadata -> m (Maybe Integer)
- findStringAttr :: Text -> Metadata -> Validation (Maybe Text)
- isPowerOfTwo :: (Num a, Bits a) => a -> Bool
- roundUpToNearestMultipleOf :: Integral n => n -> n -> n
Documentation
newtype Validation a Source #
Instances
data ValidationState Source #
ValidationState | |
|
class Monad m => MonadValidation m where Source #
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
Instances
MonadValidation Validation Source # | |
Defined in FlatBuffers.Internal.Compiler.SemanticAnalysis validating :: HasIdent a => a -> Validation b -> Validation b Source # resetContext :: Validation a -> Validation a Source # getContext :: Validation [Ident] Source # getDeclaredAttributes :: Validation (Set AttributeDecl) Source # throwErrorMsg :: String -> Validation a Source # | |
MonadValidation m => MonadValidation (StateT s m) Source # | |
Defined in FlatBuffers.Internal.Compiler.SemanticAnalysis validating :: HasIdent a => a -> StateT s m b -> StateT s m b Source # resetContext :: StateT s m a -> StateT s m a Source # getContext :: StateT s m [Ident] Source # getDeclaredAttributes :: StateT s m (Set AttributeDecl) Source # throwErrorMsg :: String -> StateT s m a Source # |
data SymbolTable enum struct table union Source #
Instances
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.
RootInfo | |
|
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_type
s.
The root type declaration can point to a table in any schema (root or imported).
getRootInfo :: Schema -> FileTree ValidDecls -> Validation (Maybe RootInfo) Source #
requiredAttr :: Text Source #
bitFlagsAttr :: Text Source #
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", ""]
validateEnums :: FileTree Stage1 -> Validation (FileTree Stage2) Source #
validateEnum :: (Namespace, Ident) -> EnumDecl -> Validation EnumDecl Source #
validateTables :: FileTree Stage3 -> Validation (FileTree Stage4) Source #
validateTable :: FileTree Stage3 -> (Namespace, Ident) -> TableDecl -> Validation TableDecl Source #
checkNoRequired :: Metadata -> Validation () Source #
checkNoDefault :: Maybe DefaultVal -> Validation () Source #
isRequired :: Metadata -> Required Source #
validateDefaultValAsInt :: forall a. (Integral a, Bounded a, Display a) => Maybe DefaultVal -> Validation (DefaultVal Integer) Source #
scientificToInteger :: forall a. (Integral a, Bounded a, Display a) => Scientific -> String -> Validation (DefaultVal Integer) Source #
validateUnion :: FileTree Stage4 -> (Namespace, Ident) -> UnionDecl -> Validation UnionDecl Source #
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.
validateStructs :: FileTree Stage2 -> Validation (FileTree Stage3) Source #
checkStructCycles :: forall m. MonadValidation 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 ValidatedStructs m, MonadValidation m) => FileTree Stage2 -> Namespace -> StructDecl -> m 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 :: (MonadValidation m, Foldable f, Functor f, HasIdent a) => f a -> m () Source #
checkUndeclaredAttributes :: (MonadValidation m, HasMetadata a) => a -> m () Source #
findIntAttr :: MonadValidation m => Text -> Metadata -> m (Maybe Integer) Source #
findStringAttr :: Text -> Metadata -> Validation (Maybe Text) Source #
roundUpToNearestMultipleOf :: Integral n => n -> n -> n Source #