Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
FileTree | |
|
Instances
Functor FileTree Source # | |
Foldable FileTree Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree fold :: Monoid m => FileTree m -> m # foldMap :: Monoid m => (a -> m) -> FileTree a -> 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 # | |
newtype StringLiteral Source #
Instances
Eq StringLiteral Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree (==) :: StringLiteral -> StringLiteral -> Bool # (/=) :: StringLiteral -> StringLiteral -> Bool # | |
Show StringLiteral Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree showsPrec :: Int -> StringLiteral -> ShowS # show :: StringLiteral -> String # showList :: [StringLiteral] -> ShowS # | |
IsString StringLiteral Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree fromString :: String -> StringLiteral # |
newtype IntLiteral Source #
Instances
data AttributeVal Source #
Instances
Eq AttributeVal Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree (==) :: AttributeVal -> AttributeVal -> Bool # (/=) :: AttributeVal -> AttributeVal -> Bool # | |
Show AttributeVal Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree showsPrec :: Int -> AttributeVal -> ShowS # show :: AttributeVal -> String # showList :: [AttributeVal] -> ShowS # |
data DefaultVal Source #
Instances
Eq DefaultVal Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree (==) :: DefaultVal -> DefaultVal -> Bool # (/=) :: DefaultVal -> DefaultVal -> Bool # | |
Show DefaultVal Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree showsPrec :: Int -> DefaultVal -> ShowS # show :: DefaultVal -> String # showList :: [DefaultVal] -> ShowS # |
newtype NamespaceDecl Source #
Instances
Eq NamespaceDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree (==) :: NamespaceDecl -> NamespaceDecl -> Bool # (/=) :: NamespaceDecl -> NamespaceDecl -> Bool # | |
Show NamespaceDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree showsPrec :: Int -> NamespaceDecl -> ShowS # show :: NamespaceDecl -> String # showList :: [NamespaceDecl] -> ShowS # | |
IsString NamespaceDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree fromString :: String -> NamespaceDecl # |
TableDecl | |
|
data TableField Source #
TableField | |
|
Instances
Eq TableField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree (==) :: TableField -> TableField -> Bool # (/=) :: TableField -> TableField -> Bool # | |
Show TableField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree showsPrec :: Int -> TableField -> ShowS # show :: TableField -> String # showList :: [TableField] -> ShowS # | |
HasMetadata TableField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree getMetadata :: TableField -> Metadata Source # | |
HasIdent TableField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree getIdent :: TableField -> Ident Source # |
data StructDecl Source #
StructDecl | |
|
Instances
Eq StructDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree (==) :: StructDecl -> StructDecl -> Bool # (/=) :: StructDecl -> StructDecl -> Bool # | |
Show StructDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree showsPrec :: Int -> StructDecl -> ShowS # show :: StructDecl -> String # showList :: [StructDecl] -> ShowS # | |
HasMetadata StructDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree getMetadata :: StructDecl -> Metadata Source # | |
HasIdent StructDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree getIdent :: StructDecl -> Ident Source # |
data StructField Source #
Instances
Eq StructField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree (==) :: StructField -> StructField -> Bool # (/=) :: StructField -> StructField -> Bool # | |
Show StructField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree showsPrec :: Int -> StructField -> ShowS # show :: StructField -> String # showList :: [StructField] -> ShowS # | |
HasMetadata StructField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree getMetadata :: StructField -> Metadata Source # | |
HasIdent StructField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree getIdent :: StructField -> Ident Source # |
EnumVal | |
|
UnionDecl | |
|
UnionVal | |
|
newtype FileIdentifierDecl Source #
Instances
Eq FileIdentifierDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree (==) :: FileIdentifierDecl -> FileIdentifierDecl -> Bool # (/=) :: FileIdentifierDecl -> FileIdentifierDecl -> Bool # | |
Show FileIdentifierDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree showsPrec :: Int -> FileIdentifierDecl -> ShowS # show :: FileIdentifierDecl -> String # showList :: [FileIdentifierDecl] -> ShowS # | |
IsString FileIdentifierDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree fromString :: String -> FileIdentifierDecl # |
newtype AttributeDecl Source #
Instances
Eq AttributeDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree (==) :: AttributeDecl -> AttributeDecl -> Bool # (/=) :: AttributeDecl -> AttributeDecl -> Bool # | |
Ord AttributeDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree 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 showsPrec :: Int -> AttributeDecl -> ShowS # show :: AttributeDecl -> String # showList :: [AttributeDecl] -> ShowS # | |
IsString AttributeDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree fromString :: String -> AttributeDecl # |
Namespace | |
|
Instances
class HasIdent a where Source #
Instances
class HasMetadata a where Source #
getMetadata :: a -> Metadata Source #
Instances
HasMetadata UnionDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree getMetadata :: UnionDecl -> Metadata Source # | |
HasMetadata EnumDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree getMetadata :: EnumDecl -> Metadata Source # | |
HasMetadata StructField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree getMetadata :: StructField -> Metadata Source # | |
HasMetadata StructDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree getMetadata :: StructDecl -> Metadata Source # | |
HasMetadata TableField Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree getMetadata :: TableField -> Metadata Source # | |
HasMetadata TableDecl Source # | |
Defined in FlatBuffers.Internal.Compiler.SyntaxTree getMetadata :: TableDecl -> Metadata Source # |