Safe Haskell | None |
---|---|
Language | Haskell2010 |
TreeSitter.Go.AST
Documentation
debugSymbolNames :: [String] Source #
type AnonymousRBrace = Token "}" 22 Source #
type AnonymousPipePipe = Token "||" 77 Source #
type AnonymousPipeEqual = Token "|=" 39 Source #
type AnonymousPipe = Token "|" 69 Source #
type AnonymousLBrace = Token "{" 21 Source #
type AnonymousVar = Token "var" 13 Source #
data TypeIdentifier a Source #
Constructors
TypeIdentifier | |
Instances
type AnonymousType = Token "type" 16 Source #
Instances
Functor True Source # | |
Foldable True Source # | |
Defined in TreeSitter.Go.AST Methods fold :: Monoid m => True m -> m # foldMap :: Monoid m => (a -> m) -> True a -> 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.Go.AST | |
Unmarshal True Source # | |
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.Go.AST type Rep (True a) = D1 ('MetaData "True" "TreeSitter.Go.AST" "tree-sitter-go-0.4.1.1-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.Go.AST type Rep1 True = D1 ('MetaData "True" "TreeSitter.Go.AST" "tree-sitter-go-0.4.1.1-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 AnonymousSwitch = Token "switch" 53 Source #
type AnonymousStruct = Token "struct" 20 Source #
type AnonymousSelect = Token "select" 56 Source #
data RuneLiteral a Source #
Constructors
RuneLiteral | |
Instances
type AnonymousReturn = Token "return" 46 Source #
data RawStringLiteral a Source #
Constructors
RawStringLiteral | |
Instances
type AnonymousRange = Token "range" 52 Source #
data PackageIdentifier a Source #
Constructors
PackageIdentifier | |
Instances
type AnonymousPackage = Token "package" 4 Source #
Instances
Functor Nil Source # | |
Foldable Nil Source # | |
Defined in TreeSitter.Go.AST Methods fold :: Monoid m => Nil m -> m # foldMap :: Monoid m => (a -> m) -> Nil a -> m # foldMap' :: Monoid m => (a -> m) -> Nil a -> m # foldr :: (a -> b -> b) -> b -> Nil a -> b # foldr' :: (a -> b -> b) -> b -> Nil a -> b # foldl :: (b -> a -> b) -> b -> Nil a -> b # foldl' :: (b -> a -> b) -> b -> Nil a -> b # foldr1 :: (a -> a -> a) -> Nil a -> a # foldl1 :: (a -> a -> a) -> Nil a -> a # elem :: Eq a => a -> Nil a -> Bool # maximum :: Ord a => Nil a -> a # | |
Traversable Nil Source # | |
SymbolMatching Nil Source # | |
Defined in TreeSitter.Go.AST | |
Unmarshal Nil Source # | |
Eq a => Eq (Nil a) Source # | |
Ord a => Ord (Nil a) Source # | |
Show a => Show (Nil a) Source # | |
Generic (Nil a) Source # | |
Generic1 Nil Source # | |
type Rep (Nil a) Source # | |
Defined in TreeSitter.Go.AST type Rep (Nil a) = D1 ('MetaData "Nil" "TreeSitter.Go.AST" "tree-sitter-go-0.4.1.1-inplace" 'False) (C1 ('MetaCons "Nil" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
type Rep1 Nil Source # | |
Defined in TreeSitter.Go.AST type Rep1 Nil = D1 ('MetaData "Nil" "TreeSitter.Go.AST" "tree-sitter-go-0.4.1.1-inplace" 'False) (C1 ('MetaCons "Nil" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
type AnonymousMap = Token "map" 24 Source #
Instances
type AnonymousInterface = Token "interface" 23 Source #
data IntLiteral a Source #
Constructors
IntLiteral | |
Instances
type AnonymousImport = Token "import" 5 Source #
data ImaginaryLiteral a Source #
Constructors
ImaginaryLiteral | |
Instances
type AnonymousIf = Token "if" 49 Source #
data Identifier a Source #
Constructors
Identifier | |
Instances
type AnonymousGoto = Token "goto" 45 Source #
type AnonymousGo = Token "go" 47 Source #
type AnonymousFunc = Token "func" 14 Source #
type AnonymousFor = Token "for" 51 Source #
data FloatLiteral a Source #
Constructors
FloatLiteral | |
Instances
data FieldIdentifier a Source #
Constructors
FieldIdentifier | |
Instances
Instances
type AnonymousFallthrough = Token "fallthrough" 42 Source #
data EscapeSequence a Source #
Constructors
EscapeSequence | |
Instances
type AnonymousElse = Token "else" 50 Source #
type AnonymousDefer = Token "defer" 48 Source #
type AnonymousDefault = Token "default" 55 Source #
type AnonymousContinue = Token "continue" 44 Source #
type AnonymousConst = Token "const" 10 Source #
type AnonymousChan = Token "chan" 25 Source #
type AnonymousCase = Token "case" 54 Source #
type AnonymousBreak = Token "break" 43 Source #
data BlankIdentifier a Source #
Constructors
BlankIdentifier | |
Instances
type AnonymousCaretEqual = Token "^=" 40 Source #
type AnonymousCaret = Token "^" 62 Source #
type AnonymousRBracket = Token "]" 19 Source #
type AnonymousLBracket = Token "[" 18 Source #
type AnonymousRAngleRAngleEqual = Token ">>=" 34 Source #
type AnonymousRAngleRAngle = Token ">>" 67 Source #
type AnonymousRAngleEqual = Token ">=" 75 Source #
type AnonymousRAngle = Token ">" 74 Source #
type AnonymousEqualEqual = Token "==" 70 Source #
type AnonymousEqual = Token "=" 12 Source #
type AnonymousLAngleEqual = Token "<=" 73 Source #
type AnonymousLAngleLAngleEqual = Token "<<=" 33 Source #
type AnonymousLAngleLAngle = Token "<<" 66 Source #
type AnonymousLAngleMinus = Token "<-" 26 Source #
type AnonymousLAngle = Token "<" 72 Source #
type AnonymousSemicolon = Token ";" 3 Source #
type AnonymousColonEqual = Token ":=" 27 Source #
type AnonymousColon = Token ":" 41 Source #
type AnonymousSlashEqual = Token "/=" 31 Source #
type AnonymousSlash = Token "/" 64 Source #
type AnonymousDotDotDot = Token "..." 15 Source #
type AnonymousDot = Token "." 6 Source #
type AnonymousMinusEqual = Token "-=" 38 Source #
type AnonymousMinusMinus = Token "--" 29 Source #
type AnonymousMinus = Token "-" 60 Source #
type AnonymousComma = Token "," 11 Source #
type AnonymousPlusEqual = Token "+=" 37 Source #
type AnonymousPlusPlus = Token "++" 28 Source #
type AnonymousPlus = Token "+" 59 Source #
type AnonymousStarEqual = Token "*=" 30 Source #
type AnonymousStar = Token "*" 17 Source #
type AnonymousRParen = Token ")" 9 Source #
type AnonymousLParen = Token "(" 8 Source #
type AnonymousAmpersandCaretEqual = Token "&^=" 36 Source #
type AnonymousAmpersandCaret = Token "&^" 68 Source #
type AnonymousAmpersandEqual = Token "&=" 35 Source #
type AnonymousAmpersandAmpersand = Token "&&" 76 Source #
type AnonymousAmpersand = Token "&" 63 Source #
type AnonymousPercentEqual = Token "%=" 32 Source #
type AnonymousPercent = Token "%" 65 Source #
type AnonymousDQuote = Token "\"" 79 Source #
type AnonymousBangEqual = Token "!=" 71 Source #
type AnonymousBang = Token "!" 61 Source #
type AnonymousLF = Token "\n" 2 Source #
data VariadicParameterDeclaration a Source #
Constructors
VariadicParameterDeclaration | |
Instances
data VariadicArgument a Source #
Constructors
VariadicArgument | |
Fields
|
Instances
Constructors
VarSpec | |
Fields
|
Instances
data VarDeclaration a Source #
Constructors
VarDeclaration | |
Fields
|
Instances
data UnaryExpression a Source #
Constructors
UnaryExpression | |
Fields
|
Instances
data TypeSwitchStatement a Source #
Constructors
TypeSwitchStatement | |
Fields
|
Instances
Instances
data TypeDeclaration a Source #
Constructors
TypeDeclaration | |
Fields
|
Instances
data TypeConversionExpression a Source #
Constructors
TypeConversionExpression | |
Fields
|
Instances
Constructors
TypeCase | |
Fields
|
Instances
data TypeAssertionExpression a Source #
Constructors
TypeAssertionExpression | |
Fields
|
Instances
Instances
data StructType a Source #
Constructors
StructType | |
Fields
|
Instances
data SourceFile a Source #
Constructors
SourceFile | |
Fields
|
Instances
Instances
data SliceExpression a Source #
Constructors
SliceExpression | |
Fields
|
Instances
data ShortVarDeclaration a Source #
Constructors
ShortVarDeclaration | |
Fields
|
Instances
data SendStatement a Source #
Constructors
SendStatement | |
Fields
|
Instances
data SelectorExpression a Source #
Constructors
SelectorExpression | |
Fields
|
Instances
data SelectStatement a Source #
Constructors
SelectStatement | |
Fields
|
Instances
data ReturnStatement a Source #
Constructors
ReturnStatement | |
Fields
|
Instances
data ReceiveStatement a Source #
Constructors
ReceiveStatement | |
Fields
|
Instances
data RangeClause a Source #
Constructors
RangeClause | |
Fields
|
Instances
data QualifiedType a Source #
Constructors
QualifiedType | |
Fields
|
Instances
data PointerType a Source #
Constructors
PointerType | |
Fields
|
Instances
data ParenthesizedType a Source #
Constructors
ParenthesizedType | |
Fields
|
Instances
data ParenthesizedExpression a Source #
Constructors
ParenthesizedExpression | |
Fields
|
Instances
data ParameterList a Source #
Constructors
ParameterList | |
Fields
|
Instances
data ParameterDeclaration a Source #
Constructors
ParameterDeclaration | |
Fields
|
Instances
data PackageClause a Source #
Constructors
PackageClause | |
Fields
|
Instances
data MethodSpecList a Source #
Constructors
MethodSpecList | |
Fields
|
Instances
data MethodSpec a Source #
Constructors
MethodSpec | |
Fields
|
Instances
data MethodDeclaration a Source #
Constructors
MethodDeclaration | |
Fields
|
Instances
Instances
data LiteralValue a Source #
Constructors
LiteralValue | |
Fields
|
Instances
data LabeledStatement a Source #
Constructors
LabeledStatement | |
Instances
data KeyedElement a Source #
Constructors
KeyedElement | |
Fields
|
Instances
data InterpretedStringLiteral a Source #
Constructors
InterpretedStringLiteral | |
Fields
|
Instances
data InterfaceType a Source #
Constructors
InterfaceType | |
Fields
|
Instances
data IndexExpression a Source #
Constructors
IndexExpression | |
Fields
|
Instances
data IncStatement a Source #
Constructors
IncStatement | |
Fields
|
Instances
data ImportSpecList a Source #
Constructors
ImportSpecList | |
Fields
|
Instances
data ImportSpec a Source #
Constructors
ImportSpec | |
Fields
|
Instances
data ImportDeclaration a Source #
Constructors
ImportDeclaration | |
Fields
|
Instances
data ImplicitLengthArrayType a Source #
Constructors
ImplicitLengthArrayType | |
Instances
data IfStatement a Source #
Constructors
IfStatement | |
Fields
|
Instances
data GotoStatement a Source #
Constructors
GotoStatement | |
Fields
|
Instances
data GoStatement a Source #
Constructors
GoStatement | |
Fields
|
Instances
data FunctionType a Source #
Constructors
FunctionType | |
Fields
|
Instances
data FunctionDeclaration a Source #
Constructors
FunctionDeclaration | |
Fields
|
Instances
data FuncLiteral a Source #
Constructors
FuncLiteral | |
Fields
|
Instances
data ForStatement a Source #
Constructors
ForStatement | |
Fields
|
Instances
Constructors
ForClause | |
Fields
|
Instances
data FieldDeclarationList a Source #
Constructors
FieldDeclarationList | |
Fields
|
Instances
data FieldDeclaration a Source #
Constructors
FieldDeclaration | |
Fields
|
Instances
data FallthroughStatement a Source #
Constructors
FallthroughStatement | |
Instances
data ExpressionSwitchStatement a Source #
Constructors
ExpressionSwitchStatement | |
Fields
|
Instances
data ExpressionList a Source #
Constructors
ExpressionList | |
Fields
|
Instances
data ExpressionCase a Source #
Constructors
ExpressionCase | |
Fields
|
Instances
data EmptyStatement a Source #
Constructors
EmptyStatement | |
Instances
Constructors
Element | |
Fields
|
Instances
Instances
Functor Dot Source # | |
Foldable Dot Source # | |
Defined in TreeSitter.Go.AST Methods fold :: Monoid m => Dot m -> m # foldMap :: Monoid m => (a -> m) -> Dot a -> m # foldMap' :: Monoid m => (a -> m) -> Dot a -> m # foldr :: (a -> b -> b) -> b -> Dot a -> b # foldr' :: (a -> b -> b) -> b -> Dot a -> b # foldl :: (b -> a -> b) -> b -> Dot a -> b # foldl' :: (b -> a -> b) -> b -> Dot a -> b # foldr1 :: (a -> a -> a) -> Dot a -> a # foldl1 :: (a -> a -> a) -> Dot a -> a # elem :: Eq a => a -> Dot a -> Bool # maximum :: Ord a => Dot a -> a # | |
Traversable Dot Source # | |
SymbolMatching Dot Source # | |
Defined in TreeSitter.Go.AST | |
Unmarshal Dot Source # | |
Eq a => Eq (Dot a) Source # | |
Ord a => Ord (Dot a) Source # | |
Show a => Show (Dot a) Source # | |
Generic (Dot a) Source # | |
Generic1 Dot Source # | |
type Rep (Dot a) Source # | |
Defined in TreeSitter.Go.AST type Rep (Dot a) = D1 ('MetaData "Dot" "TreeSitter.Go.AST" "tree-sitter-go-0.4.1.1-inplace" 'False) (C1 ('MetaCons "Dot" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
type Rep1 Dot Source # | |
Defined in TreeSitter.Go.AST type Rep1 Dot = D1 ('MetaData "Dot" "TreeSitter.Go.AST" "tree-sitter-go-0.4.1.1-inplace" 'False) (C1 ('MetaCons "Dot" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
data DeferStatement a Source #
Constructors
DeferStatement | |
Fields
|
Instances
data DefaultCase a Source #
Constructors
DefaultCase | |
Fields
|
Instances
data DecStatement a Source #
Constructors
DecStatement | |
Fields
|
Instances
data ContinueStatement a Source #
Constructors
ContinueStatement | |
Fields
|
Instances
Constructors
ConstSpec | |
Fields
|
Instances
data ConstDeclaration a Source #
Constructors
ConstDeclaration | |
Fields
|
Instances
data CompositeLiteral a Source #
Constructors
CompositeLiteral | |
Fields
|
Instances
data CommunicationCase a Source #
Constructors
CommunicationCase | |
Fields
|
Instances
data ChannelType a Source #
Constructors
ChannelType | |
Instances
data CallExpression a Source #
Constructors
CallExpression | |
Fields
|
Instances
data BreakStatement a Source #
Constructors
BreakStatement | |
Fields
|
Instances
Constructors
Block | |
Fields
|
Instances
Functor Block Source # | |
Foldable Block Source # | |
Defined in TreeSitter.Go.AST Methods fold :: Monoid m => Block m -> m # foldMap :: Monoid m => (a -> m) -> Block a -> 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.Go.AST | |
Unmarshal Block Source # | |
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.Go.AST type Rep (Block a) = D1 ('MetaData "Block" "TreeSitter.Go.AST" "tree-sitter-go-0.4.1.1-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.Go.AST type Rep1 Block = D1 ('MetaData "Block" "TreeSitter.Go.AST" "tree-sitter-go-0.4.1.1-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
data AssignmentStatement a Source #
Constructors
Instances
Instances
data ArgumentList a Source #
Constructors
ArgumentList | |
Fields
|
Instances
Constructors
Type | |
Fields
|
Instances
Functor Type Source # | |
Foldable Type Source # | |
Defined in TreeSitter.Go.AST Methods fold :: Monoid m => Type m -> m # foldMap :: Monoid m => (a -> m) -> Type a -> 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.Go.AST | |
Unmarshal Type Source # | |
HasField "ann" (Type a) a Source # | |
Defined in TreeSitter.Go.AST | |
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.Go.AST type Rep (Type a) = D1 ('MetaData "Type" "TreeSitter.Go.AST" "tree-sitter-go-0.4.1.1-inplace" 'True) (C1 ('MetaCons "Type" 'PrefixI 'True) (S1 ('MetaSel ('Just "getType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((SimpleType :+: ParenthesizedType) a)))) | |
type Rep1 Type Source # | |
Defined in TreeSitter.Go.AST type Rep1 Type = D1 ('MetaData "Type" "TreeSitter.Go.AST" "tree-sitter-go-0.4.1.1-inplace" 'True) (C1 ('MetaCons "Type" 'PrefixI 'True) (S1 ('MetaSel ('Just "getType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (SimpleType :+: ParenthesizedType)))) |
Constructors
Instances
newtype SimpleType a Source #
Constructors
SimpleType | |
Fields
|
Instances
newtype SimpleStatement a Source #
Constructors
SimpleStatement | |
Fields |
Instances
newtype Expression a Source #
Constructors