| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
FlatBuffers.Internal.Compiler.SyntaxTree
Documentation
Constructors
| FileTree | |
Fields
| |
Instances
| Functor FileTree Source # | |
| Foldable FileTree Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods fold :: Monoid m => FileTree m -> m # foldMap :: Monoid m => (a -> m) -> FileTree a -> m # foldr :: (a -> b -> b) -> b -> FileTree a -> b # foldr' :: (a -> b -> b) -> b -> FileTree a -> b # foldl :: (b -> a -> b) -> b -> FileTree a -> b # foldl' :: (b -> a -> b) -> b -> FileTree a -> b # foldr1 :: (a -> a -> a) -> FileTree a -> a # foldl1 :: (a -> a -> a) -> FileTree a -> a # elem :: Eq a => a -> FileTree a -> Bool # maximum :: Ord a => FileTree a -> a # minimum :: Ord a => FileTree a -> a # | |
| Traversable FileTree Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree | |
| Eq a => Eq (FileTree a) Source # | |
| Show a => Show (FileTree a) Source # | |
Constructors
| DeclN !NamespaceDecl | |
| DeclT !TableDecl | |
| DeclS !StructDecl | |
| DeclE !EnumDecl | |
| DeclU !UnionDecl | |
| DeclR !RootDecl | |
| DeclFI !FileIdentifierDecl | |
| DeclA !AttributeDecl |
Constructors
| Include | |
Fields | |
newtype StringLiteral Source #
Constructors
| StringLiteral | |
Fields | |
Instances
| Eq StringLiteral Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods (==) :: StringLiteral -> StringLiteral -> Bool # (/=) :: StringLiteral -> StringLiteral -> Bool # | |
| Show StringLiteral Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods showsPrec :: Int -> StringLiteral -> ShowS # show :: StringLiteral -> String # showList :: [StringLiteral] -> ShowS # | |
| IsString StringLiteral Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods fromString :: String -> StringLiteral # | |
newtype IntLiteral Source #
Constructors
| IntLiteral | |
Fields | |
Instances
data AttributeVal Source #
Instances
| Eq AttributeVal Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree | |
| Show AttributeVal Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods showsPrec :: Int -> AttributeVal -> ShowS # show :: AttributeVal -> String # showList :: [AttributeVal] -> ShowS # | |
data DefaultVal Source #
Constructors
| DefaultNum !Scientific | |
| DefaultBool !Bool | |
| DefaultRef !(NonEmpty Text) |
Instances
| Eq DefaultVal Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree | |
| Show DefaultVal Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods showsPrec :: Int -> DefaultVal -> ShowS # show :: DefaultVal -> String # showList :: [DefaultVal] -> ShowS # | |
Constructors
| Metadata | |
Fields
| |
newtype NamespaceDecl Source #
Constructors
| NamespaceDecl | |
Fields | |
Instances
| Eq NamespaceDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods (==) :: NamespaceDecl -> NamespaceDecl -> Bool # (/=) :: NamespaceDecl -> NamespaceDecl -> Bool # | |
| Show NamespaceDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods showsPrec :: Int -> NamespaceDecl -> ShowS # show :: NamespaceDecl -> String # showList :: [NamespaceDecl] -> ShowS # | |
| IsString NamespaceDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods fromString :: String -> NamespaceDecl # | |
Constructors
| TableDecl | |
Fields
| |
data TableField Source #
Constructors
| TableField | |
Fields
| |
Instances
| Eq TableField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree | |
| Show TableField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods showsPrec :: Int -> TableField -> ShowS # show :: TableField -> String # showList :: [TableField] -> ShowS # | |
| HasMetadata TableField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods getMetadata :: TableField -> Metadata Source # | |
| HasIdent TableField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods getIdent :: TableField -> Ident Source # | |
data StructDecl Source #
Constructors
| StructDecl | |
Fields
| |
Instances
| Eq StructDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree | |
| Show StructDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods showsPrec :: Int -> StructDecl -> ShowS # show :: StructDecl -> String # showList :: [StructDecl] -> ShowS # | |
| HasMetadata StructDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods getMetadata :: StructDecl -> Metadata Source # | |
| HasIdent StructDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods getIdent :: StructDecl -> Ident Source # | |
data StructField Source #
Constructors
| StructField | |
Fields
| |
Instances
| Eq StructField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree | |
| Show StructField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods showsPrec :: Int -> StructField -> ShowS # show :: StructField -> String # showList :: [StructField] -> ShowS # | |
| HasMetadata StructField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods getMetadata :: StructField -> Metadata Source # | |
| HasIdent StructField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods getIdent :: StructField -> Ident Source # | |
Constructors
| EnumDecl | |
Constructors
| EnumVal | |
Fields
| |
Constructors
| UnionDecl | |
Fields
| |
Constructors
| UnionVal | |
Fields
| |
Constructors
| TInt8 | |
| TInt16 | |
| TInt32 | |
| TInt64 | |
| TWord8 | |
| TWord16 | |
| TWord32 | |
| TWord64 | |
| TFloat | |
| TDouble | |
| TBool | |
| TString | |
| TRef !TypeRef | |
| TVector !Type |
Constructors
| TypeRef | |
Fields
| |
newtype FileIdentifierDecl Source #
Constructors
| FileIdentifierDecl Text |
Instances
| Eq FileIdentifierDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods (==) :: FileIdentifierDecl -> FileIdentifierDecl -> Bool # (/=) :: FileIdentifierDecl -> FileIdentifierDecl -> Bool # | |
| Show FileIdentifierDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods showsPrec :: Int -> FileIdentifierDecl -> ShowS # show :: FileIdentifierDecl -> String # showList :: [FileIdentifierDecl] -> ShowS # | |
| IsString FileIdentifierDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods fromString :: String -> FileIdentifierDecl # | |
newtype AttributeDecl Source #
Constructors
| AttributeDecl Text |
Instances
| Eq AttributeDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods (==) :: AttributeDecl -> AttributeDecl -> Bool # (/=) :: AttributeDecl -> AttributeDecl -> Bool # | |
| Ord AttributeDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods compare :: AttributeDecl -> AttributeDecl -> Ordering # (<) :: AttributeDecl -> AttributeDecl -> Bool # (<=) :: AttributeDecl -> AttributeDecl -> Bool # (>) :: AttributeDecl -> AttributeDecl -> Bool # (>=) :: AttributeDecl -> AttributeDecl -> Bool # max :: AttributeDecl -> AttributeDecl -> AttributeDecl # min :: AttributeDecl -> AttributeDecl -> AttributeDecl # | |
| Show AttributeDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods showsPrec :: Int -> AttributeDecl -> ShowS # show :: AttributeDecl -> String # showList :: [AttributeDecl] -> ShowS # | |
| IsString AttributeDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods fromString :: String -> AttributeDecl # | |
Constructors
| Namespace | |
Fields
| |
Instances
| Eq Namespace Source # | |
| Ord Namespace Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree | |
| Show Namespace Source # | |
| IsString Namespace Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods fromString :: String -> Namespace # | |
| Semigroup Namespace Source # | |
| Display Namespace Source # | |
class HasIdent a where Source #
Instances
class HasMetadata a where Source #
Methods
getMetadata :: a -> Metadata Source #
Instances
| HasMetadata UnionDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods getMetadata :: UnionDecl -> Metadata Source # | |
| HasMetadata EnumDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods getMetadata :: EnumDecl -> Metadata Source # | |
| HasMetadata StructField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods getMetadata :: StructField -> Metadata Source # | |
| HasMetadata StructDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods getMetadata :: StructDecl -> Metadata Source # | |
| HasMetadata TableField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods getMetadata :: TableField -> Metadata Source # | |
| HasMetadata TableDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree Methods getMetadata :: TableDecl -> Metadata Source # | |