Safe Haskell | None |
---|---|
Language | Haskell2010 |
TreeSitter.Java.AST
Documentation
newtype AnonymousTilde a Source #
Constructors
AnonymousTilde | |
Fields
|
Instances
newtype AnonymousRBrace a Source #
Constructors
AnonymousRBrace | |
Fields
|
Instances
newtype AnonymousPipePipe a Source #
Constructors
AnonymousPipePipe | |
Fields
|
Instances
newtype AnonymousPipeEqual a Source #
Constructors
AnonymousPipeEqual | |
Fields
|
Instances
newtype AnonymousPipe a Source #
Constructors
AnonymousPipe | |
Fields
|
Instances
newtype AnonymousLBrace a Source #
Constructors
AnonymousLBrace | |
Fields
|
Instances
newtype AnonymousWith a Source #
Constructors
AnonymousWith | |
Fields
|
Instances
newtype AnonymousWhile a Source #
Constructors
AnonymousWhile | |
Fields
|
Instances
newtype AnonymousVolatile a Source #
Constructors
AnonymousVolatile | |
Fields
|
Instances
Instances
newtype AnonymousUses a Source #
Constructors
AnonymousUses | |
Fields
|
Instances
data TypeIdentifier a Source #
Constructors
TypeIdentifier | |
Instances
newtype AnonymousTry a Source #
Constructors
AnonymousTry | |
Fields
|
Instances
Instances
Functor True Source # | |
Foldable True Source # | |
Defined in TreeSitter.Java.AST Methods fold :: Monoid m => True m -> m # foldMap :: Monoid m => (a -> m) -> True a -> m # foldr :: (a -> b -> b) -> b -> True a -> b # foldr' :: (a -> b -> b) -> b -> True a -> b # foldl :: (b -> a -> b) -> b -> True a -> b # foldl' :: (b -> a -> b) -> b -> True a -> b # foldr1 :: (a -> a -> a) -> True a -> a # foldl1 :: (a -> a -> a) -> True a -> a # elem :: Eq a => a -> True a -> Bool # maximum :: Ord a => True a -> a # | |
Traversable True Source # | |
SymbolMatching True Source # | |
Defined in TreeSitter.Java.AST | |
Unmarshal True Source # | |
Defined in TreeSitter.Java.AST Methods unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (True a) | |
Eq a => Eq (True a) Source # | |
Ord a => Ord (True a) Source # | |
Show a => Show (True a) Source # | |
Generic (True a) Source # | |
Generic1 True Source # | |
type Rep (True a) Source # | |
Defined in TreeSitter.Java.AST type Rep (True a) = D1 (MetaData "True" "TreeSitter.Java.AST" "tree-sitter-java-0.3.0.0-inplace" False) (C1 (MetaCons "True" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) | |
type Rep1 True Source # | |
Defined in TreeSitter.Java.AST type Rep1 True = D1 (MetaData "True" "TreeSitter.Java.AST" "tree-sitter-java-0.3.0.0-inplace" False) (C1 (MetaCons "True" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
newtype AnonymousTransitive a Source #
Constructors
AnonymousTransitive | |
Fields
|
Instances
newtype AnonymousTransient a Source #
Constructors
AnonymousTransient | |
Fields
|
Instances
newtype AnonymousTo a Source #
Constructors
AnonymousTo | |
Fields
|
Instances
newtype AnonymousThrows a Source #
Constructors
AnonymousThrows | |
Fields
|
Instances
newtype AnonymousThrow a Source #
Constructors
AnonymousThrow | |
Fields
|
Instances
Instances
Functor This Source # | |
Foldable This Source # | |
Defined in TreeSitter.Java.AST Methods fold :: Monoid m => This m -> m # foldMap :: Monoid m => (a -> m) -> This a -> m # foldr :: (a -> b -> b) -> b -> This a -> b # foldr' :: (a -> b -> b) -> b -> This a -> b # foldl :: (b -> a -> b) -> b -> This a -> b # foldl' :: (b -> a -> b) -> b -> This a -> b # foldr1 :: (a -> a -> a) -> This a -> a # foldl1 :: (a -> a -> a) -> This a -> a # elem :: Eq a => a -> This a -> Bool # maximum :: Ord a => This a -> a # | |
Traversable This Source # | |
SymbolMatching This Source # | |
Defined in TreeSitter.Java.AST | |
Unmarshal This Source # | |
Defined in TreeSitter.Java.AST Methods unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (This a) | |
Eq a => Eq (This a) Source # | |
Ord a => Ord (This a) Source # | |
Show a => Show (This a) Source # | |
Generic (This a) Source # | |
Generic1 This Source # | |
type Rep (This a) Source # | |
Defined in TreeSitter.Java.AST type Rep (This a) = D1 (MetaData "This" "TreeSitter.Java.AST" "tree-sitter-java-0.3.0.0-inplace" False) (C1 (MetaCons "This" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) | |
type Rep1 This Source # | |
Defined in TreeSitter.Java.AST type Rep1 This = D1 (MetaData "This" "TreeSitter.Java.AST" "tree-sitter-java-0.3.0.0-inplace" False) (C1 (MetaCons "This" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
newtype AnonymousSynchronized a Source #
Constructors
AnonymousSynchronized | |
Fields
|
Instances
newtype AnonymousSwitch a Source #
Constructors
AnonymousSwitch | |
Fields
|
Instances
Instances
Functor Super Source # | |
Foldable Super Source # | |
Defined in TreeSitter.Java.AST Methods fold :: Monoid m => Super m -> m # foldMap :: Monoid m => (a -> m) -> Super a -> m # foldr :: (a -> b -> b) -> b -> Super a -> b # foldr' :: (a -> b -> b) -> b -> Super a -> b # foldl :: (b -> a -> b) -> b -> Super a -> b # foldl' :: (b -> a -> b) -> b -> Super a -> b # foldr1 :: (a -> a -> a) -> Super a -> a # foldl1 :: (a -> a -> a) -> Super a -> a # elem :: Eq a => a -> Super a -> Bool # maximum :: Ord a => Super a -> a # minimum :: Ord a => Super a -> a # | |
Traversable Super Source # | |
SymbolMatching Super Source # | |
Defined in TreeSitter.Java.AST | |
Unmarshal Super Source # | |
Defined in TreeSitter.Java.AST Methods unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Super a) | |
Eq a => Eq (Super a) Source # | |
Ord a => Ord (Super a) Source # | |
Show a => Show (Super a) Source # | |
Generic (Super a) Source # | |
Generic1 Super Source # | |
type Rep (Super a) Source # | |
Defined in TreeSitter.Java.AST type Rep (Super a) = D1 (MetaData "Super" "TreeSitter.Java.AST" "tree-sitter-java-0.3.0.0-inplace" False) (C1 (MetaCons "Super" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) | |
type Rep1 Super Source # | |
Defined in TreeSitter.Java.AST type Rep1 Super = D1 (MetaData "Super" "TreeSitter.Java.AST" "tree-sitter-java-0.3.0.0-inplace" False) (C1 (MetaCons "Super" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
data StringLiteral a Source #
Constructors
StringLiteral | |
Instances
newtype AnonymousStrictfp a Source #
Constructors
AnonymousStrictfp | |
Fields
|
Instances
newtype AnonymousStatic a Source #
Constructors
AnonymousStatic | |
Fields
|
Instances
newtype AnonymousShort a Source #
Constructors
AnonymousShort | |
Fields
|
Instances
newtype AnonymousReturn a Source #
Constructors
AnonymousReturn | |
Fields
|
Instances
newtype AnonymousRequires a Source #
Constructors
AnonymousRequires | |
Fields
|
Instances
newtype AnonymousPublic a Source #
Constructors
AnonymousPublic | |
Fields
|
Instances
newtype AnonymousProvides a Source #
Constructors
AnonymousProvides | |
Fields
|
Instances
newtype AnonymousProtected a Source #
Constructors
AnonymousProtected | |
Fields
|
Instances
newtype AnonymousPrivate a Source #
Constructors
AnonymousPrivate | |
Fields
|
Instances
newtype AnonymousPackage a Source #
Constructors
AnonymousPackage | |
Fields
|
Instances
newtype AnonymousOpens a Source #
Constructors
AnonymousOpens | |
Fields
|
Instances
newtype AnonymousOpen a Source #
Constructors
AnonymousOpen | |
Fields
|
Instances
data OctalIntegerLiteral a Source #
Constructors
OctalIntegerLiteral | |
Instances
data NullLiteral a Source #
Constructors
NullLiteral | |
Instances
newtype AnonymousNew a Source #
Constructors
AnonymousNew | |
Fields
|
Instances
newtype AnonymousNative a Source #
Constructors
AnonymousNative | |
Fields
|
Instances
newtype AnonymousModule a Source #
Constructors
AnonymousModule | |
Fields
|
Instances
newtype AnonymousLong a Source #
Constructors
AnonymousLong | |
Fields
|
Instances
newtype AnonymousInterface a Source #
Constructors
AnonymousInterface | |
Fields
|
Instances
newtype AnonymousInt a Source #
Constructors
AnonymousInt | |
Fields
|
Instances
newtype AnonymousInstanceof a Source #
Constructors
AnonymousInstanceof | |
Fields
|
Instances
newtype AnonymousImport a Source #
Constructors
AnonymousImport | |
Fields
|
Instances
newtype AnonymousImplements a Source #
Constructors
AnonymousImplements | |
Fields
|
Instances
newtype AnonymousIf a Source #
Constructors
AnonymousIf | |
Fields
|
Instances
data Identifier a Source #
Constructors
Identifier | |
Instances
data HexIntegerLiteral a Source #
Constructors
HexIntegerLiteral | |
Instances
data HexFloatingPointLiteral a Source #
Constructors
HexFloatingPointLiteral | |
Instances
newtype AnonymousFor a Source #
Constructors
AnonymousFor | |
Fields
|
Instances
newtype AnonymousFloat a Source #
Constructors
AnonymousFloat | |
Fields
|
Instances
newtype AnonymousFinally a Source #
Constructors
AnonymousFinally | |
Fields
|
Instances
newtype AnonymousFinal a Source #
Constructors
AnonymousFinal | |
Fields
|
Instances
Instances
Functor False Source # | |
Foldable False Source # | |
Defined in TreeSitter.Java.AST Methods fold :: Monoid m => False m -> m # foldMap :: Monoid m => (a -> m) -> False a -> m # foldr :: (a -> b -> b) -> b -> False a -> b # foldr' :: (a -> b -> b) -> b -> False a -> b # foldl :: (b -> a -> b) -> b -> False a -> b # foldl' :: (b -> a -> b) -> b -> False a -> b # foldr1 :: (a -> a -> a) -> False a -> a # foldl1 :: (a -> a -> a) -> False a -> a # elem :: Eq a => a -> False a -> Bool # maximum :: Ord a => False a -> a # minimum :: Ord a => False a -> a # | |
Traversable False Source # | |
SymbolMatching False Source # | |
Defined in TreeSitter.Java.AST | |
Unmarshal False Source # | |
Defined in TreeSitter.Java.AST Methods unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (False a) | |
Eq a => Eq (False a) Source # | |
Ord a => Ord (False a) Source # | |
Show a => Show (False a) Source # | |
Generic (False a) Source # | |
Generic1 False Source # | |
type Rep (False a) Source # | |
Defined in TreeSitter.Java.AST type Rep (False a) = D1 (MetaData "False" "TreeSitter.Java.AST" "tree-sitter-java-0.3.0.0-inplace" False) (C1 (MetaCons "False" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) | |
type Rep1 False Source # | |
Defined in TreeSitter.Java.AST type Rep1 False = D1 (MetaData "False" "TreeSitter.Java.AST" "tree-sitter-java-0.3.0.0-inplace" False) (C1 (MetaCons "False" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
newtype AnonymousExtends a Source #
Constructors
AnonymousExtends | |
Fields
|
Instances
newtype AnonymousExports a Source #
Constructors
AnonymousExports | |
Fields
|
Instances
newtype AnonymousEnum a Source #
Constructors
AnonymousEnum | |
Fields
|
Instances
newtype AnonymousElse a Source #
Constructors
AnonymousElse | |
Fields
|
Instances
newtype AnonymousDouble a Source #
Constructors
AnonymousDouble | |
Fields
|
Instances
newtype AnonymousDo a Source #
Constructors
AnonymousDo | |
Fields
|
Instances
newtype AnonymousDefault a Source #
Constructors
AnonymousDefault | |
Fields
|
Instances
data DecimalIntegerLiteral a Source #
Constructors
DecimalIntegerLiteral | |
Instances
data DecimalFloatingPointLiteral a Source #
Constructors
DecimalFloatingPointLiteral | |
Instances
newtype AnonymousContinue a Source #
Constructors
AnonymousContinue | |
Fields
|
Instances
newtype AnonymousClass a Source #
Constructors
AnonymousClass | |
Fields
|
Instances
data CharacterLiteral a Source #
Constructors
CharacterLiteral | |
Instances
newtype AnonymousChar a Source #
Constructors
AnonymousChar | |
Fields
|
Instances
newtype AnonymousCatch a Source #
Constructors
AnonymousCatch | |
Fields
|
Instances
newtype AnonymousCase a Source #
Constructors
AnonymousCase | |
Fields
|
Instances
newtype AnonymousByte a Source #
Constructors
AnonymousByte | |
Fields
|
Instances
newtype AnonymousBreak a Source #
Constructors
AnonymousBreak | |
Fields
|
Instances
data BooleanType a Source #
Constructors
BooleanType | |
Instances
data BinaryIntegerLiteral a Source #
Constructors
BinaryIntegerLiteral | |
Instances
newtype AnonymousAssert a Source #
Constructors
AnonymousAssert | |
Fields
|
Instances
newtype AnonymousAbstract a Source #
Constructors
AnonymousAbstract | |
Fields
|
Instances
newtype AnonymousCaretEqual a Source #
Constructors
AnonymousCaretEqual | |
Fields
|
Instances
newtype AnonymousCaret a Source #
Constructors
AnonymousCaret | |
Fields
|
Instances
newtype AnonymousRBracket a Source #
Constructors
AnonymousRBracket | |
Fields
|
Instances
newtype AnonymousLBracket a Source #
Constructors
AnonymousLBracket | |
Fields
|
Instances
newtype AnonymousAtinterface a Source #
Constructors
AnonymousAtinterface | |
Fields
|
Instances
newtype AnonymousAt a Source #
Constructors
AnonymousAt | |
Fields
|
Instances
newtype AnonymousQuestion a Source #
Constructors
AnonymousQuestion | |
Fields
|
Instances
newtype AnonymousRAngleRAngleRAngleEqual a Source #
Constructors
AnonymousRAngleRAngleRAngleEqual | |
Fields
|
Instances
newtype AnonymousRAngleRAngleRAngle a Source #
Constructors
AnonymousRAngleRAngleRAngle | |
Fields
|
Instances
newtype AnonymousRAngleRAngleEqual a Source #
Constructors
AnonymousRAngleRAngleEqual | |
Fields
|
Instances
newtype AnonymousRAngleRAngle a Source #
Constructors
AnonymousRAngleRAngle | |
Fields
|
Instances
newtype AnonymousRAngleEqual a Source #
Constructors
AnonymousRAngleEqual | |
Fields
|
Instances
newtype AnonymousRAngle a Source #
Constructors
AnonymousRAngle | |
Fields
|
Instances
newtype AnonymousEqualEqual a Source #
Constructors
AnonymousEqualEqual | |
Fields
|
Instances
newtype AnonymousEqual a Source #
Constructors
AnonymousEqual | |
Fields
|
Instances
newtype AnonymousLAngleEqual a Source #
Constructors
AnonymousLAngleEqual | |
Fields
|
Instances
newtype AnonymousLAngleLAngleEqual a Source #
Constructors
AnonymousLAngleLAngleEqual | |
Fields
|
Instances
newtype AnonymousLAngleLAngle a Source #
Constructors
AnonymousLAngleLAngle | |
Fields
|
Instances
newtype AnonymousLAngle a Source #
Constructors
AnonymousLAngle | |
Fields
|
Instances
newtype AnonymousSemicolon a Source #
Constructors
AnonymousSemicolon | |
Fields
|
Instances
newtype AnonymousColonColon a Source #
Constructors
AnonymousColonColon | |
Fields
|
Instances
newtype AnonymousColon a Source #
Constructors
AnonymousColon | |
Fields
|
Instances
newtype AnonymousSlashEqual a Source #
Constructors
AnonymousSlashEqual | |
Fields
|
Instances
newtype AnonymousSlash a Source #
Constructors
AnonymousSlash | |
Fields
|
Instances
newtype AnonymousDotDotDot a Source #
Constructors
AnonymousDotDotDot | |
Fields
|
Instances
newtype AnonymousDot a Source #
Constructors
AnonymousDot | |
Fields
|
Instances
newtype AnonymousMinusRAngle a Source #
Constructors
AnonymousMinusRAngle | |
Fields
|
Instances
newtype AnonymousMinusEqual a Source #
Constructors
AnonymousMinusEqual | |
Fields
|
Instances
newtype AnonymousMinusMinus a Source #
Constructors
AnonymousMinusMinus | |
Fields
|
Instances
newtype AnonymousMinus a Source #
Constructors
AnonymousMinus | |
Fields
|
Instances
newtype AnonymousComma a Source #
Constructors
AnonymousComma | |
Fields
|
Instances
newtype AnonymousPlusEqual a Source #
Constructors
AnonymousPlusEqual | |
Fields
|
Instances
newtype AnonymousPlusPlus a Source #
Constructors
AnonymousPlusPlus | |
Fields
|
Instances
newtype AnonymousPlus a Source #
Constructors
AnonymousPlus | |
Fields
|
Instances
newtype AnonymousStarEqual a Source #
Constructors
AnonymousStarEqual | |
Fields
|
Instances
newtype AnonymousStar a Source #
Constructors
AnonymousStar | |
Fields
|
Instances
newtype AnonymousRParen a Source #
Constructors
AnonymousRParen | |
Fields
|
Instances
newtype AnonymousLParen a Source #
Constructors
AnonymousLParen | |
Fields
|
Instances
newtype AnonymousAmpersandEqual a Source #
Constructors
AnonymousAmpersandEqual | |
Fields
|
Instances
newtype AnonymousAmpersandAmpersand a Source #
Constructors
AnonymousAmpersandAmpersand | |
Fields
|
Instances
newtype AnonymousAmpersand a Source #
Constructors
AnonymousAmpersand | |
Fields
|
Instances
newtype AnonymousPercentEqual a Source #
Constructors
AnonymousPercentEqual | |
Fields
|
Instances
newtype AnonymousPercent a Source #
Constructors
AnonymousPercent | |
Fields
|
Instances
newtype AnonymousBangEqual a Source #
Constructors
AnonymousBangEqual | |
Fields
|
Instances
newtype AnonymousBang a Source #
Constructors
AnonymousBang | |
Fields
|
Instances
Constructors
Wildcard | |
Fields
|
Instances
data WhileStatement a Source #
Constructors
WhileStatement | |
Fields
|
Instances
data VariableDeclarator a Source #
Constructors
VariableDeclarator | |
Fields
|
Instances
data UpdateExpression a Source #
Constructors
UpdateExpression | |
Fields
|
Instances
data UnaryExpression a Source #
Constructors
UnaryExpression | |
Fields
|
Instances
data TypeParameters a Source #
Constructors
TypeParameters | |
Fields
|
Instances
data TypeParameter a Source #
Constructors
TypeParameter | |
Fields
|
Instances
Constructors
TypeBound | |
Fields
|
Instances
data TypeArguments a Source #
Constructors
TypeArguments | |
Fields
|
Instances
data TryWithResourcesStatement a Source #
Constructors
TryWithResourcesStatement | |
Fields
|
Instances
data TryStatement a Source #
Constructors
TryStatement | |
Fields
|
Instances
Constructors
Throws | |
Fields
|
Instances
data ThrowStatement a Source #
Constructors
ThrowStatement | |
Fields
|
Instances
data TernaryExpression a Source #
Constructors
TernaryExpression | |
Fields
|
Instances
data SynchronizedStatement a Source #
Constructors
SynchronizedStatement | |
Fields
|
Instances
data SwitchStatement a Source #
Constructors
SwitchStatement | |
Fields
|
Instances
data SwitchLabel a Source #
Constructors
SwitchLabel | |
Fields
|
Instances
data SwitchBlock a Source #
Constructors
SwitchBlock | |
Fields
|
Instances
data Superclass a Source #
Constructors
Superclass | |
Fields
|
Instances
data SuperInterfaces a Source #
Constructors
SuperInterfaces | |
Fields
|
Instances
data StaticInitializer a Source #
Constructors
StaticInitializer | |
Fields
|
Instances
data SpreadParameter a Source #
Constructors
SpreadParameter | |
Fields
|
Instances
data ScopedTypeIdentifier a Source #
Constructors
ScopedTypeIdentifier | |
Fields
|
Instances
data ScopedIdentifier a Source #
Constructors
ScopedIdentifier | |
Fields
|
Instances
data ReturnStatement a Source #
Constructors
ReturnStatement | |
Fields
|
Instances
data ResourceSpecification a Source #
Constructors
ResourceSpecification | |
Fields
|
Instances
Constructors
Resource | |
Fields
|
Instances
data RequiresModifier a Source #
Constructors
RequiresModifier | |
Instances
data ReceiverParameter a Source #
Constructors
ReceiverParameter | |
Fields
|
Instances
Constructors
Program | |
Fields
|
Instances
data ParenthesizedExpression a Source #
Constructors
ParenthesizedExpression | |
Fields
|
Instances
data PackageDeclaration a Source #
Constructors
PackageDeclaration | |
Fields
|
Instances
data ObjectCreationExpression a Source #
Constructors
ObjectCreationExpression | |
Fields
|
Instances
data ModuleName a Source #
Constructors
ModuleName | |
Fields
|
Instances
data ModuleDirective a Source #
Constructors
ModuleDirective | |
Fields
|
Instances
data ModuleDeclaration a Source #
Constructors
ModuleDeclaration | |
Fields
|
Instances
Constructors
Modifiers | |
Fields
|
Instances
data MethodReference a Source #
Constructors
MethodReference | |
Fields
|
Instances
data MethodInvocation a Source #
Constructors
MethodInvocation | |
Fields
|
Instances
data MethodDeclaration a Source #
Constructors
MethodDeclaration | |
Fields
|
Instances
data MarkerAnnotation a Source #
Constructors
MarkerAnnotation | |
Fields
|
Instances
data LocalVariableDeclarationStatement a Source #
Constructors
LocalVariableDeclarationStatement | |
Fields
|
Instances
data LocalVariableDeclaration a Source #
Constructors
LocalVariableDeclaration | |
Fields
|
Instances
data LambdaExpression a Source #
Constructors
LambdaExpression | |
Fields
|
Instances
data LabeledStatement a Source #
Constructors
LabeledStatement | |
Fields
|
Instances
data InterfaceTypeList a Source #
Constructors
InterfaceTypeList | |
Fields
|
Instances
data InterfaceDeclaration a Source #
Constructors
InterfaceDeclaration | |
Fields
|
Instances
data InterfaceBody a Source #
Constructors
InterfaceBody | |
Fields |
Instances
data IntegralType a Source #
Constructors
IntegralType | |
Instances
data InstanceofExpression a Source #
Constructors
InstanceofExpression | |
Fields
|
Instances
data InferredParameters a Source #
Constructors
InferredParameters | |
Fields
|
Instances
data ImportDeclaration a Source #
Constructors
ImportDeclaration | |
Fields
|
Instances
data IfStatement a Source #
Constructors
IfStatement | |
Fields
|
Instances
data GenericType a Source #
Constructors
GenericType | |
Fields
|
Instances
data FormalParameters a Source #
Constructors
FormalParameters | |
Fields
|
Instances
data FormalParameter a Source #
Constructors
FormalParameter | |
Fields
|
Instances
data ForStatement a Source #
Constructors
ForStatement | |
Fields
|
Instances
Constructors
ForInit | |
Fields
|
Instances
data FloatingPointType a Source #
Constructors
FloatingPointType | |
Instances
data FinallyClause a Source #
Constructors
FinallyClause | |
Fields
|
Instances
data FieldDeclaration a Source #
Constructors
FieldDeclaration | |
Fields
|
Instances
data FieldAccess a Source #
Constructors
FieldAccess | |
Fields
|
Instances
data ExtendsInterfaces a Source #
Constructors
ExtendsInterfaces | |
Fields
|
Instances
data ExpressionStatement a Source #
Constructors
ExpressionStatement | |
Fields
|
Instances
data ExplicitConstructorInvocation a Source #
Constructors
ExplicitConstructorInvocation | |
Fields
|
Instances
data EnumDeclaration a Source #
Constructors
EnumDeclaration | |
Fields
|
Instances
data EnumConstant a Source #
Constructors
EnumConstant | |
Fields
|
Instances
data EnumBodyDeclarations a Source #
Constructors
EnumBodyDeclarations | |
Fields |
Instances
Constructors
EnumBody | |
Fields
|
Instances
data EnhancedForStatement a Source #
Constructors
EnhancedForStatement | |
Fields
|
Instances
data ElementValuePair a Source #
Constructors
ElementValuePair | |
Fields
|
Instances
data ElementValueArrayInitializer a Source #
Constructors
ElementValueArrayInitializer | |
Fields
|
Instances
data DoStatement a Source #
Constructors
DoStatement | |
Fields
|
Instances
data DimensionsExpr a Source #
Constructors
DimensionsExpr | |
Fields
|
Instances
data Dimensions a Source #
Constructors
Dimensions | |
Fields
|
Instances
data ContinueStatement a Source #
Constructors
ContinueStatement | |
Fields
|
Instances
data ConstructorDeclaration a Source #
Constructors
ConstructorDeclaration | |
Fields
|
Instances
data ConstructorBody a Source #
Constructors
ConstructorBody | |
Fields
|
Instances
data ConstantDeclaration a Source #
Constructors
ConstantDeclaration | |
Fields
|
Instances
data ClassLiteral a Source #
Constructors
ClassLiteral | |
Fields
|
Instances
data ClassDeclaration a Source #
Constructors
ClassDeclaration | |
Fields
|
Instances
Constructors
ClassBody | |
Fields |
Instances
Constructors
CatchType | |
Fields
|
Instances
data CatchFormalParameter a Source #
Constructors
CatchFormalParameter | |
Fields
|
Instances
data CatchClause a Source #
Constructors
CatchClause | |
Fields
|
Instances
data CastExpression a Source #
Constructors
CastExpression | |
Fields
|
Instances
data BreakStatement a Source #
Constructors
BreakStatement | |
Fields
|
Instances
Constructors
Block | |
Fields
|
Instances
Functor Block Source # | |
Foldable Block Source # | |
Defined in TreeSitter.Java.AST Methods fold :: Monoid m => Block m -> m # foldMap :: Monoid m => (a -> m) -> Block a -> m # foldr :: (a -> b -> b) -> b -> Block a -> b # foldr' :: (a -> b -> b) -> b -> Block a -> b # foldl :: (b -> a -> b) -> b -> Block a -> b # foldl' :: (b -> a -> b) -> b -> Block a -> b # foldr1 :: (a -> a -> a) -> Block a -> a # foldl1 :: (a -> a -> a) -> Block a -> a # elem :: Eq a => a -> Block a -> Bool # maximum :: Ord a => Block a -> a # minimum :: Ord a => Block a -> a # | |
Traversable Block Source # | |
SymbolMatching Block Source # | |
Defined in TreeSitter.Java.AST | |
Unmarshal Block Source # | |
Defined in TreeSitter.Java.AST Methods unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Block a) | |
Eq a => Eq (Block a) Source # | |
Ord a => Ord (Block a) Source # | |
Show a => Show (Block a) Source # | |
Generic (Block a) Source # | |
Generic1 Block Source # | |
type Rep (Block a) Source # | |
Defined in TreeSitter.Java.AST type Rep (Block a) = D1 (MetaData "Block" "TreeSitter.Java.AST" "tree-sitter-java-0.3.0.0-inplace" False) (C1 (MetaCons "Block" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Statement a]))) | |
type Rep1 Block Source # | |
Defined in TreeSitter.Java.AST type Rep1 Block = D1 (MetaData "Block" "TreeSitter.Java.AST" "tree-sitter-java-0.3.0.0-inplace" False) (C1 (MetaCons "Block" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 Statement))) |
data BinaryExpression a Source #
Constructors
Instances
Instances
data AssignmentExpression a Source #
Constructors
Instances
data AssertStatement a Source #
Constructors
AssertStatement | |
Fields
|
Instances
Constructors
ArrayType | |
Fields
|
Instances
data ArrayInitializer a Source #
Constructors
ArrayInitializer | |
Fields
|
Instances
data ArrayCreationExpression a Source #
Constructors
ArrayCreationExpression | |
Fields
|
Instances
data ArrayAccess a Source #
Constructors
ArrayAccess | |
Fields
|
Instances
data ArgumentList a Source #
Constructors
ArgumentList | |
Fields
|
Instances
data AnnotationTypeElementDeclaration a Source #
Constructors
AnnotationTypeElementDeclaration | |
Fields
|
Instances
data AnnotationTypeDeclaration a Source #
Constructors
AnnotationTypeDeclaration | |
Fields
|
Instances
data AnnotationTypeBody a Source #
Constructors
AnnotationTypeBody | |
Fields |
Instances
data AnnotationArgumentList a Source #
Constructors
AnnotationArgumentList | |
Fields
|
Instances
data Annotation a Source #
Constructors
Annotation | |
Fields
|
Instances
data AnnotatedType a Source #
Constructors
AnnotatedType | |
Fields
|
Instances
data UnannotatedType a Source #
Constructors
Instances
Constructors
UnannotatedTypeType (UnannotatedType a) | |
AnnotatedTypeType (AnnotatedType a) |
Instances
Constructors
Instances
data SimpleType a Source #
Constructors
Instances
Constructors
Instances
Constructors
Instances
data Expression a Source #
Constructors
Instances
data Declaration a Source #
Constructors