Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
type AnonymousTilde = Token "~" 52 Source #
type AnonymousRBrace = Token "}" 64 Source #
type AnonymousPipePipe = Token "||" 35 Source #
type AnonymousPipeEqual = Token "|=" 22 Source #
type AnonymousPipe = Token "|" 40 Source #
type AnonymousLBrace = Token "{" 63 Source #
type AnonymousWith = Token "with" 91 Source #
type AnonymousWhile = Token "while" 70 Source #
type AnonymousVolatile = Token "volatile" 105 Source #
Instances
type AnonymousUses = Token "uses" 89 Source #
data TypeIdentifier a Source #
Instances
type AnonymousTry = Token "try" 76 Source #
Instances
Functor True Source # | |
Foldable True Source # | |
Defined in TreeSitter.Java.AST 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 symbolMatch :: Proxy True -> Node -> Bool showFailure :: Proxy True -> Node -> String | |
Unmarshal True Source # | |
Defined in TreeSitter.Java.AST 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.4.0.0-inplace" False) (C1 (MetaCons "True" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "text") 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.4.0.0-inplace" False) (C1 (MetaCons "True" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
type AnonymousTransitive = Token "transitive" 92 Source #
type AnonymousTransient = Token "transient" 104 Source #
type AnonymousTo = Token "to" 87 Source #
type AnonymousThrows = Token "throws" 119 Source #
type AnonymousThrow = Token "throw" 75 Source #
Instances
Functor This Source # | |
Foldable This Source # | |
Defined in TreeSitter.Java.AST 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 symbolMatch :: Proxy This -> Node -> Bool showFailure :: Proxy This -> Node -> String | |
Unmarshal This Source # | |
Defined in TreeSitter.Java.AST 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.4.0.0-inplace" False) (C1 (MetaCons "This" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "text") 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.4.0.0-inplace" False) (C1 (MetaCons "This" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
type AnonymousSynchronized = Token "synchronized" 74 Source #
type AnonymousSwitch = Token "switch" 66 Source #
Instances
data StringLiteral a Source #
Instances
type AnonymousStrictfp = Token "strictfp" 102 Source #
type AnonymousStatic = Token "static" 93 Source #
type AnonymousShort = Token "short" 110 Source #
type AnonymousReturn = Token "return" 73 Source #
type AnonymousRequires = Token "requires" 85 Source #
type AnonymousPublic = Token "public" 97 Source #
type AnonymousProvides = Token "provides" 90 Source #
type AnonymousProtected = Token "protected" 98 Source #
type AnonymousPrivate = Token "private" 99 Source #
type AnonymousPackage = Token "package" 94 Source #
type AnonymousOpens = Token "opens" 88 Source #
type AnonymousOpen = Token "open" 83 Source #
data OctalIntegerLiteral a Source #
Instances
data NullLiteral a Source #
Instances
type AnonymousNew = Token "new" 55 Source #
type AnonymousNative = Token "native" 103 Source #
type AnonymousModule = Token "module" 84 Source #
type AnonymousLong = Token "long" 112 Source #
type AnonymousInterface = Token "interface" 108 Source #
type AnonymousInt = Token "int" 111 Source #
type AnonymousInstanceof = Token "instanceof" 46 Source #
type AnonymousImport = Token "import" 95 Source #
type AnonymousImplements = Token "implements" 106 Source #
type AnonymousIf = Token "if" 79 Source #
data Identifier a Source #
Instances
data HexIntegerLiteral a Source #
Instances
data HexFloatingPointLiteral a Source #
Instances
type AnonymousFor = Token "for" 81 Source #
type AnonymousFloat = Token "float" 114 Source #
type AnonymousFinally = Token "finally" 78 Source #
type AnonymousFinal = Token "final" 101 Source #
Instances
type AnonymousExtends = Token "extends" 61 Source #
type AnonymousExports = Token "exports" 86 Source #
type AnonymousEnum = Token "enum" 96 Source #
type AnonymousElse = Token "else" 80 Source #
type AnonymousDouble = Token "double" 115 Source #
type AnonymousDo = Token "do" 69 Source #
type AnonymousDefault = Token "default" 68 Source #
data DecimalIntegerLiteral a Source #
Instances
data DecimalFloatingPointLiteral a Source #
Instances
type AnonymousContinue = Token "continue" 72 Source #
type AnonymousClass = Token "class" 59 Source #
data CharacterLiteral a Source #
Instances
type AnonymousChar = Token "char" 113 Source #
type AnonymousCatch = Token "catch" 77 Source #
type AnonymousCase = Token "case" 67 Source #
type AnonymousByte = Token "byte" 109 Source #
type AnonymousBreak = Token "break" 71 Source #
data BooleanType a Source #
Instances
data BinaryIntegerLiteral a Source #
Instances
type AnonymousAssert = Token "assert" 65 Source #
type AnonymousAbstract = Token "abstract" 100 Source #
type AnonymousCaretEqual = Token "^=" 23 Source #
type AnonymousCaret = Token "^" 41 Source #
type AnonymousRBracket = Token "]" 57 Source #
type AnonymousLBracket = Token "[" 56 Source #
type AnonymousAtinterface = Token "@interface" 107 Source #
type AnonymousAt = Token "@" 82 Source #
type AnonymousQuestion = Token "?" 49 Source #
type AnonymousRAngleRAngleRAngleEqual = Token ">>>=" 27 Source #
type AnonymousRAngleRAngleRAngle = Token ">>>" 45 Source #
type AnonymousRAngleRAngleEqual = Token ">>=" 26 Source #
type AnonymousRAngleRAngle = Token ">>" 44 Source #
type AnonymousRAngleEqual = Token ">=" 31 Source #
type AnonymousRAngle = Token ">" 28 Source #
type AnonymousEqualEqual = Token "==" 30 Source #
type AnonymousEqual = Token "=" 16 Source #
type AnonymousLAngleEqual = Token "<=" 32 Source #
type AnonymousLAngleLAngleEqual = Token "<<=" 25 Source #
type AnonymousLAngleLAngle = Token "<<" 43 Source #
type AnonymousLAngle = Token "<" 29 Source #
type AnonymousSemicolon = Token ";" 62 Source #
type AnonymousColonColon = Token "::" 60 Source #
type AnonymousColon = Token ":" 50 Source #
type AnonymousSlashEqual = Token "/=" 20 Source #
type AnonymousSlash = Token "/" 39 Source #
type AnonymousDotDotDot = Token "..." 118 Source #
type AnonymousDot = Token "." 58 Source #
type AnonymousMinusRAngle = Token "->" 47 Source #
type AnonymousMinusEqual = Token "-=" 18 Source #
type AnonymousMinusMinus = Token "--" 54 Source #
type AnonymousMinus = Token "-" 37 Source #
type AnonymousComma = Token "," 48 Source #
type AnonymousPlusEqual = Token "+=" 17 Source #
type AnonymousPlusPlus = Token "++" 53 Source #
type AnonymousPlus = Token "+" 36 Source #
type AnonymousStarEqual = Token "*=" 19 Source #
type AnonymousStar = Token "*" 38 Source #
type AnonymousRParen = Token ")" 15 Source #
type AnonymousLParen = Token "(" 13 Source #
type AnonymousAmpersandEqual = Token "&=" 21 Source #
type AnonymousAmpersandAmpersand = Token "&&" 34 Source #
type AnonymousAmpersand = Token "&" 14 Source #
type AnonymousPercentEqual = Token "%=" 24 Source #
type AnonymousPercent = Token "%" 42 Source #
type AnonymousBangEqual = Token "!=" 33 Source #
type AnonymousBang = Token "!" 51 Source #
Wildcard | |
|
Instances
data WhileStatement a Source #
WhileStatement | |
|
Instances
data VariableDeclarator a Source #
VariableDeclarator | |
|
Instances
data UpdateExpression a Source #
UpdateExpression | |
|
Instances
data UnaryExpression a Source #
UnaryExpression | |
|
Instances
data TypeParameters a Source #
TypeParameters | |
|
Instances
data TypeParameter a Source #
TypeParameter | |
|
Instances
TypeBound | |
|
Instances
data TypeArguments a Source #
TypeArguments | |
|
Instances
data TryWithResourcesStatement a Source #
TryWithResourcesStatement | |
|
Instances
data TryStatement a Source #
TryStatement | |
|
Instances
Throws | |
|
Instances
data ThrowStatement a Source #
ThrowStatement | |
|
Instances
data TernaryExpression a Source #
TernaryExpression | |
|
Instances
data SynchronizedStatement a Source #
SynchronizedStatement | |
|
Instances
data SwitchStatement a Source #
SwitchStatement | |
|
Instances
data SwitchLabel a Source #
SwitchLabel | |
|
Instances
data SwitchBlock a Source #
SwitchBlock | |
|
Instances
data Superclass a Source #
Superclass | |
|
Instances
data SuperInterfaces a Source #
SuperInterfaces | |
|
Instances
data StaticInitializer a Source #
StaticInitializer | |
|
Instances
data SpreadParameter a Source #
SpreadParameter | |
|
Instances
data ScopedTypeIdentifier a Source #
ScopedTypeIdentifier | |
|
Instances
data ScopedIdentifier a Source #
ScopedIdentifier | |
|
Instances
data ReturnStatement a Source #
ReturnStatement | |
|
Instances
data ResourceSpecification a Source #
ResourceSpecification | |
|
Instances
Resource | |
|
Instances
data RequiresModifier a Source #
Instances
data ReceiverParameter a Source #
ReceiverParameter | |
|
Instances
Program | |
|
Instances
data ParenthesizedExpression a Source #
ParenthesizedExpression | |
|
Instances
data PackageDeclaration a Source #
PackageDeclaration | |
|
Instances
data ObjectCreationExpression a Source #
ObjectCreationExpression | |
|
Instances
data ModuleName a Source #
ModuleName | |
|
Instances
data ModuleDirective a Source #
ModuleDirective | |
|
Instances
data ModuleDeclaration a Source #
ModuleDeclaration | |
|
Instances
Modifiers | |
|
Instances
data MethodReference a Source #
MethodReference | |
|
Instances
data MethodInvocation a Source #
MethodInvocation | |
|
Instances
data MethodDeclaration a Source #
MethodDeclaration | |
|
Instances
data MarkerAnnotation a Source #
MarkerAnnotation | |
|
Instances
data LocalVariableDeclarationStatement a Source #
Instances
data LocalVariableDeclaration a Source #
LocalVariableDeclaration | |
|
Instances
data LambdaExpression a Source #
LambdaExpression | |
|
Instances
data LabeledStatement a Source #
LabeledStatement | |
|
Instances
data InterfaceTypeList a Source #
InterfaceTypeList | |
|
Instances
data InterfaceDeclaration a Source #
InterfaceDeclaration | |
|
Instances
data InterfaceBody a Source #
Instances
data IntegralType a Source #
Instances
data InstanceofExpression a Source #
InstanceofExpression | |
|
Instances
data InferredParameters a Source #
InferredParameters | |
|
Instances
data ImportDeclaration a Source #
ImportDeclaration | |
|
Instances
data IfStatement a Source #
IfStatement | |
|
Instances
data GenericType a Source #
GenericType | |
|
Instances
data FormalParameters a Source #
FormalParameters | |
|
Instances
data FormalParameter a Source #
FormalParameter | |
|
Instances
data ForStatement a Source #
ForStatement | |
|
Instances
ForInit | |
|
Instances
data FloatingPointType a Source #
Instances
data FinallyClause a Source #
FinallyClause | |
|
Instances
data FieldDeclaration a Source #
FieldDeclaration | |
|
Instances
data FieldAccess a Source #
FieldAccess | |
|
Instances
data ExtendsInterfaces a Source #
ExtendsInterfaces | |
|
Instances
data ExpressionStatement a Source #
ExpressionStatement | |
|
Instances
data ExplicitConstructorInvocation a Source #
ExplicitConstructorInvocation | |
|
Instances
data EnumDeclaration a Source #
EnumDeclaration | |
|
Instances
data EnumConstant a Source #
EnumConstant | |
|
Instances
data EnumBodyDeclarations a Source #
Instances
EnumBody | |
|
Instances
data EnhancedForStatement a Source #
EnhancedForStatement | |
|
Instances
data ElementValuePair a Source #
ElementValuePair | |
|
Instances
data ElementValueArrayInitializer a Source #
ElementValueArrayInitializer | |
|
Instances
data DoStatement a Source #
DoStatement | |
|
Instances
data DimensionsExpr a Source #
DimensionsExpr | |
|
Instances
data Dimensions a Source #
Dimensions | |
|
Instances
data ContinueStatement a Source #
ContinueStatement | |
|
Instances
data ConstructorDeclaration a Source #
ConstructorDeclaration | |
|
Instances
data ConstructorBody a Source #
ConstructorBody | |
|
Instances
data ConstantDeclaration a Source #
ConstantDeclaration | |
|
Instances
data ClassLiteral a Source #
ClassLiteral | |
|
Instances
data ClassDeclaration a Source #
ClassDeclaration | |
|
Instances
Instances
CatchType | |
|
Instances
data CatchFormalParameter a Source #
CatchFormalParameter | |
|
Instances
data CatchClause a Source #
CatchClause | |
|
Instances
data CastExpression a Source #
CastExpression | |
|
Instances
data BreakStatement a Source #
BreakStatement | |
|
Instances
Block | |
|
Instances
data BinaryExpression a Source #
Instances
Instances
data AssignmentExpression a Source #
Instances
data AssertStatement a Source #
AssertStatement | |
|
Instances
ArrayType | |
|
Instances
data ArrayInitializer a Source #
ArrayInitializer | |
|
Instances
data ArrayCreationExpression a Source #
ArrayCreationExpression | |
|
Instances
data ArrayAccess a Source #
ArrayAccess | |
|
Instances
data ArgumentList a Source #
ArgumentList | |
|
Instances
data AnnotationTypeElementDeclaration a Source #
AnnotationTypeElementDeclaration | |
|
Instances
data AnnotationTypeDeclaration a Source #
AnnotationTypeDeclaration | |
|
Instances
data AnnotationTypeBody a Source #
Instances
data AnnotationArgumentList a Source #
AnnotationArgumentList | |
|
Instances
data Annotation a Source #
Annotation | |
|
Instances
data AnnotatedType a Source #
AnnotatedType | |
|
Instances
newtype UnannotatedType a Source #
UnannotatedType ((:+:) ((:+:) ((:+:) ArrayType BooleanType) ((:+:) FloatingPointType GenericType)) ((:+:) ((:+:) IntegralType ScopedTypeIdentifier) ((:+:) TypeIdentifier VoidType)) a) |
Instances
Instances
Functor Type Source # | |
Foldable Type Source # | |
Defined in TreeSitter.Java.AST fold :: Monoid m => Type m -> m # foldMap :: Monoid m => (a -> m) -> Type a -> m # foldr :: (a -> b -> b) -> b -> Type a -> b # foldr' :: (a -> b -> b) -> b -> Type a -> b # foldl :: (b -> a -> b) -> b -> Type a -> b # foldl' :: (b -> a -> b) -> b -> Type a -> b # foldr1 :: (a -> a -> a) -> Type a -> a # foldl1 :: (a -> a -> a) -> Type a -> a # elem :: Eq a => a -> Type a -> Bool # maximum :: Ord a => Type a -> a # | |
Traversable Type Source # | |
SymbolMatching Type Source # | |
Defined in TreeSitter.Java.AST symbolMatch :: Proxy Type -> Node -> Bool showFailure :: Proxy Type -> Node -> String | |
Unmarshal Type Source # | |
Defined in TreeSitter.Java.AST unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Type a) | |
Eq a => Eq (Type a) Source # | |
Ord a => Ord (Type a) Source # | |
Show a => Show (Type a) Source # | |
Generic (Type a) Source # | |
Generic1 Type Source # | |
type Rep (Type a) Source # | |
Defined in TreeSitter.Java.AST type Rep (Type a) = D1 (MetaData "Type" "TreeSitter.Java.AST" "tree-sitter-java-0.4.0.0-inplace" True) (C1 (MetaCons "Type" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((UnannotatedType :+: AnnotatedType) a)))) | |
type Rep1 Type Source # | |
Defined in TreeSitter.Java.AST type Rep1 Type = D1 (MetaData "Type" "TreeSitter.Java.AST" "tree-sitter-java-0.4.0.0-inplace" True) (C1 (MetaCons "Type" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 (UnannotatedType :+: AnnotatedType)))) |
Instances
newtype SimpleType a Source #
SimpleType ((:+:) ((:+:) BooleanType ((:+:) FloatingPointType GenericType)) ((:+:) ((:+:) IntegralType ScopedTypeIdentifier) ((:+:) TypeIdentifier VoidType)) a) |
Instances
Instances
Instances
newtype Expression a Source #
Instances
newtype Declaration a Source #
Declaration ((:+:) ((:+:) AnnotationTypeDeclaration ((:+:) ClassDeclaration EnumDeclaration)) ((:+:) ((:+:) ImportDeclaration InterfaceDeclaration) ((:+:) ModuleDeclaration PackageDeclaration)) a) |