Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
newtype BreakStatement Source #
Instances
newtype ContinueStatement Source #
Instances
newtype ImportPrefix Source #
Instances
newtype PassStatement Source #
Instances
newtype WildcardImport Source #
Instances
data AnonymousImport Source #
Instances
data AnonymousDot Source #
Instances
data AnonymousFrom Source #
Instances
data AnonymousFuture Source #
Instances
data AnonymousLParen Source #
Instances
data AnonymousRParen Source #
Instances
data AnonymousComma Source #
Instances
data AnonymousAs Source #
Instances
data AnonymousStar Source #
Instances
data AnonymousPrint Source #
Instances
data AnonymousRAngleRAngle Source #
Instances
data AnonymousAssert Source #
Instances
data AnonymousColonEqual Source #
Instances
data AnonymousReturn Source #
Instances
data AnonymousDel Source #
Instances
data AnonymousRaise Source #
Instances
data AnonymousPass Source #
Instances
data AnonymousBreak Source #
Instances
data AnonymousContinue Source #
Instances
data AnonymousIf Source #
Instances
data AnonymousColon Source #
Instances
data AnonymousElif Source #
Instances
data AnonymousElse Source #
Instances
data AnonymousAsync Source #
Instances
data AnonymousFor Source #
Instances
data AnonymousIn Source #
Instances
data AnonymousWhile Source #
Instances
data AnonymousTry Source #
Instances
data AnonymousExcept Source #
Instances
data AnonymousFinally Source #
Instances
data AnonymousWith Source #
Instances
data AnonymousDef Source #
Instances
data AnonymousMinusRAngle Source #
Instances
data AnonymousEqual Source #
Instances
data AnonymousGlobal Source #
Instances
data AnonymousNonlocal Source #
Instances
data AnonymousExec Source #
Instances
data AnonymousClass Source #
Instances
data AnonymousAt Source #
Instances
data AnonymousNot Source #
Instances
data AnonymousAnd Source #
Instances
data AnonymousOr Source #
Instances
data AnonymousPlus Source #
Instances
data AnonymousMinus Source #
Instances
data AnonymousSlash Source #
Instances
data AnonymousPercent Source #
Instances
data AnonymousSlashSlash Source #
Instances
data AnonymousStarStar Source #
Instances
data AnonymousPipe Source #
Instances
data AnonymousAmpersand Source #
Instances
data AnonymousCaret Source #
Instances
data AnonymousLAngleLAngle Source #
Instances
data AnonymousTilde Source #
Instances
data AnonymousLAngle Source #
Instances
data AnonymousLAngleEqual Source #
Instances
data AnonymousEqualEqual Source #
Instances
data AnonymousBangEqual Source #
Instances
data AnonymousRAngleEqual Source #
Instances
data AnonymousRAngle Source #
Instances
data AnonymousLAngleRAngle Source #
Instances
data AnonymousIs Source #
Instances
data AnonymousLambda Source #
Instances
data AnonymousPlusEqual Source #
Instances
data AnonymousMinusEqual Source #
Instances
data AnonymousStarEqual Source #
Instances
data AnonymousSlashEqual Source #
Instances
data AnonymousAtEqual Source #
Instances
data AnonymousSlashSlashEqual Source #
Instances
data AnonymousPercentEqual Source #
Instances
data AnonymousStarStarEqual Source #
Instances
data AnonymousRAngleRAngleEqual Source #
Instances
data AnonymousLAngleLAngleEqual Source #
Instances
data AnonymousAmpersandEqual Source #
Instances
data AnonymousCaretEqual Source #
Instances
data AnonymousPipeEqual Source #
Instances
data AnonymousYield Source #
Instances
data AnonymousLBracket Source #
Instances
data AnonymousRBracket Source #
Instances
Instances
Eq Ellipsis Source # | |
Ord Ellipsis Source # | |
Defined in TreeSitter.Python.AST | |
Show Ellipsis Source # | |
Generic Ellipsis Source # | |
Unmarshal Ellipsis Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Ellipsis | |
SymbolMatching Ellipsis Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Ellipsis -> Node -> Bool showFailure :: Proxy Ellipsis -> Node -> String | |
type Rep Ellipsis Source # | |
Defined in TreeSitter.Python.AST |
data AnonymousLBrace Source #
Instances
data AnonymousRBrace Source #
Instances
newtype EscapeSequence Source #
Instances
newtype TypeConversion Source #
Instances
Instances
Eq Integer Source # | |
Ord Integer Source # | |
Show Integer Source # | |
Generic Integer Source # | |
Unmarshal Integer Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Integer | |
SymbolMatching Integer Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Integer -> Node -> Bool showFailure :: Proxy Integer -> Node -> String | |
type Rep Integer Source # | |
Defined in TreeSitter.Python.AST |
Instances
Eq Float Source # | |
Ord Float Source # | |
Show Float Source # | |
Generic Float Source # | |
Unmarshal Float Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Float | |
SymbolMatching Float Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Float -> Node -> Bool showFailure :: Proxy Float -> Node -> String | |
type Rep Float Source # | |
Defined in TreeSitter.Python.AST |
newtype Identifier Source #
Instances
data NonlocalStatement Source #
NonlocalStatement | |
|
Instances
data GlobalStatement Source #
GlobalStatement | |
|
Instances
data DottedName Source #
DottedName | |
|
Instances
data RelativeImport Source #
RelativeImport | |
|
Instances
data AliasedImport Source #
Instances
data ImportStatement Source #
ImportStatement | |
|
Instances
data ImportFromStatement Source #
ImportFromStatement | |
|
Instances
data FutureImportStatement Source #
FutureImportStatement | |
|
Instances
Instances
Eq True Source # | |
Ord True Source # | |
Show True Source # | |
Generic True Source # | |
Unmarshal True Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m True | |
SymbolMatching True Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy True -> Node -> Bool showFailure :: Proxy True -> Node -> String | |
type Rep True Source # | |
Defined in TreeSitter.Python.AST |
Instances
Eq False Source # | |
Ord False Source # | |
Show False Source # | |
Generic False Source # | |
Unmarshal False Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m False | |
SymbolMatching False Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy False -> Node -> Bool showFailure :: Proxy False -> Node -> String | |
type Rep False Source # | |
Defined in TreeSitter.Python.AST |
Instances
Eq None Source # | |
Ord None Source # | |
Show None Source # | |
Generic None Source # | |
Unmarshal None Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m None | |
SymbolMatching None Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy None -> Node -> Bool showFailure :: Proxy None -> Node -> String | |
type Rep None Source # | |
Defined in TreeSitter.Python.AST |
data PrimaryExpression Source #
Instances
data UnaryOperator Source #
Instances
Tuple | |
|
Instances
Eq Tuple Source # | |
Ord Tuple Source # | |
Show Tuple Source # | |
Generic Tuple Source # | |
Unmarshal Tuple Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Tuple | |
SymbolMatching Tuple Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Tuple -> Node -> Bool showFailure :: Proxy Tuple -> Node -> String | |
type Rep Tuple Source # | |
Defined in TreeSitter.Python.AST type Rep Tuple = D1 (MetaData "Tuple" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Tuple" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either Expression Yield]))) |
Yield | |
|
Instances
Eq Yield Source # | |
Ord Yield Source # | |
Show Yield Source # | |
Generic Yield Source # | |
Unmarshal Yield Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Yield | |
SymbolMatching Yield Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Yield -> Node -> Bool showFailure :: Proxy Yield -> Node -> String | |
type Rep Yield Source # | |
Defined in TreeSitter.Python.AST type Rep Yield = D1 (MetaData "Yield" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Yield" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either Expression ExpressionList]))) |
data ExpressionList Source #
ExpressionList | |
|
Instances
data Expression Source #
Instances
data NotOperator Source #
Instances
data NamedExpression Source #
NamedExpression | |
|
Instances
Lambda | |
|
Instances
Eq Lambda Source # | |
Ord Lambda Source # | |
Show Lambda Source # | |
Generic Lambda Source # | |
Unmarshal Lambda Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Lambda | |
SymbolMatching Lambda Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Lambda -> Node -> Bool showFailure :: Proxy Lambda -> Node -> String | |
type Rep Lambda Source # | |
Defined in TreeSitter.Python.AST type Rep Lambda = D1 (MetaData "Lambda" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Lambda" PrefixI True) (S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either Expression Lambda)) :*: S1 (MetaSel (Just "parameters") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LambdaParameters)))) |
data LambdaParameters Source #
Instances
data TypedParameter Source #
TypedParameter | |
|
Instances
Type | |
|
Instances
Eq Type Source # | |
Ord Type Source # | |
Show Type Source # | |
Generic Type Source # | |
Unmarshal Type Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Type | |
SymbolMatching Type Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Type -> Node -> Bool showFailure :: Proxy Type -> Node -> String | |
type Rep Type Source # | |
Defined in TreeSitter.Python.AST type Rep Type = D1 (MetaData "Type" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Type" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Expression]))) |
ListSplat | |
|
Instances
Eq ListSplat Source # | |
Ord ListSplat Source # | |
Defined in TreeSitter.Python.AST | |
Show ListSplat Source # | |
Generic ListSplat Source # | |
Unmarshal ListSplat Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m ListSplat | |
SymbolMatching ListSplat Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy ListSplat -> Node -> Bool showFailure :: Proxy ListSplat -> Node -> String | |
type Rep ListSplat Source # | |
Defined in TreeSitter.Python.AST type Rep ListSplat = D1 (MetaData "ListSplat" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "ListSplat" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Expression]))) |
data DictionarySplat Source #
DictionarySplat | |
|
Instances
data TypedDefaultParameter Source #
TypedDefaultParameter | |
|
Instances
data DefaultParameter Source #
DefaultParameter | |
|
Instances
data ConditionalExpression Source #
Instances
data ComparisonOperator Source #
Instances
data BooleanOperator Source #
BooleanOperator | |
|
Instances
Await | |
|
Instances
Eq Await Source # | |
Ord Await Source # | |
Show Await Source # | |
Generic Await Source # | |
Unmarshal Await Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Await | |
SymbolMatching Await Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Await -> Node -> Bool showFailure :: Proxy Await -> Node -> String | |
type Rep Await Source # | |
Defined in TreeSitter.Python.AST type Rep Await = D1 (MetaData "Await" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Await" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Expression]))) |
Subscript | |
|
Instances
Eq Subscript Source # | |
Ord Subscript Source # | |
Defined in TreeSitter.Python.AST | |
Show Subscript Source # | |
Generic Subscript Source # | |
Unmarshal Subscript Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Subscript | |
SymbolMatching Subscript Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Subscript -> Node -> Bool showFailure :: Proxy Subscript -> Node -> String | |
type Rep Subscript Source # | |
Defined in TreeSitter.Python.AST type Rep Subscript = D1 (MetaData "Subscript" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Subscript" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either Expression (Either PrimaryExpression Slice)]))) |
Slice | |
|
Instances
Eq Slice Source # | |
Ord Slice Source # | |
Show Slice Source # | |
Generic Slice Source # | |
Unmarshal Slice Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Slice | |
SymbolMatching Slice Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Slice -> Node -> Bool showFailure :: Proxy Slice -> Node -> String | |
type Rep Slice Source # | |
Defined in TreeSitter.Python.AST type Rep Slice = D1 (MetaData "Slice" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Slice" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Expression]))) |
String | |
|
Instances
Eq String Source # | |
Ord String Source # | |
Show String Source # | |
Generic String Source # | |
Unmarshal String Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m String | |
SymbolMatching String Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy String -> Node -> Bool showFailure :: Proxy String -> Node -> String0 | |
type Rep String Source # | |
Defined in TreeSitter.Python.AST type Rep String = D1 (MetaData "String" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "String" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either EscapeSequence Interpolation]))) |
data Interpolation Source #
Instances
data FormatSpecifier Source #
Instances
data FormatExpression Source #
FormatExpression | |
|
Instances
data SetComprehension Source #
SetComprehension | |
|
Instances
IfClause | |
|
Instances
Eq IfClause Source # | |
Ord IfClause Source # | |
Defined in TreeSitter.Python.AST | |
Show IfClause Source # | |
Generic IfClause Source # | |
Unmarshal IfClause Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m IfClause | |
SymbolMatching IfClause Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy IfClause -> Node -> Bool showFailure :: Proxy IfClause -> Node -> String | |
type Rep IfClause Source # | |
Defined in TreeSitter.Python.AST type Rep IfClause = D1 (MetaData "IfClause" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "IfClause" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Expression]))) |
data ForInClause Source #
ForInClause | |
|
Instances
Variables | |
|
Instances
Eq Variables Source # | |
Ord Variables Source # | |
Defined in TreeSitter.Python.AST | |
Show Variables Source # | |
Generic Variables Source # | |
Unmarshal Variables Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Variables | |
SymbolMatching Variables Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Variables -> Node -> Bool showFailure :: Proxy Variables -> Node -> String | |
type Rep Variables Source # | |
Defined in TreeSitter.Python.AST type Rep Variables = D1 (MetaData "Variables" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Variables" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PrimaryExpression]))) |
Set | |
|
Instances
Eq Set Source # | |
Ord Set Source # | |
Show Set Source # | |
Generic Set Source # | |
Unmarshal Set Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Set | |
SymbolMatching Set Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Set -> Node -> Bool showFailure :: Proxy Set -> Node -> String | |
type Rep Set Source # | |
Defined in TreeSitter.Python.AST type Rep Set = D1 (MetaData "Set" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Set" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either Expression ListSplat]))) |
data ParenthesizedExpression Source #
Instances
data ListComprehension Source #
ListComprehension | |
|
Instances
List | |
|
Instances
Eq List Source # | |
Ord List Source # | |
Show List Source # | |
Generic List Source # | |
Unmarshal List Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m List | |
SymbolMatching List Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy List -> Node -> Bool showFailure :: Proxy List -> Node -> String | |
type Rep List Source # | |
Defined in TreeSitter.Python.AST type Rep List = D1 (MetaData "List" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "List" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either Expression ListSplat]))) |
data GeneratorExpression Source #
Instances
data DictionaryComprehension Source #
DictionaryComprehension | |
|
Instances
Pair | |
|
Instances
Eq Pair Source # | |
Ord Pair Source # | |
Show Pair Source # | |
Generic Pair Source # | |
Unmarshal Pair Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Pair | |
SymbolMatching Pair Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Pair -> Node -> Bool showFailure :: Proxy Pair -> Node -> String | |
type Rep Pair Source # | |
Defined in TreeSitter.Python.AST type Rep Pair = D1 (MetaData "Pair" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Pair" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Expression]))) |
data Dictionary Source #
Dictionary | |
|
Instances
data ConcatenatedString Source #
ConcatenatedString | |
|
Instances
Instances
Eq Call Source # | |
Ord Call Source # | |
Show Call Source # | |
Generic Call Source # | |
Unmarshal Call Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Call | |
SymbolMatching Call Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Call -> Node -> Bool showFailure :: Proxy Call -> Node -> String | |
type Rep Call Source # | |
Defined in TreeSitter.Python.AST type Rep Call = D1 (MetaData "Call" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Call" PrefixI True) (S1 (MetaSel (Just "function") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PrimaryExpression) :*: S1 (MetaSel (Just "arguments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either ArgumentList GeneratorExpression)))) |
data ArgumentList Source #
ArgumentList | |
|
Instances
data KeywordArgument Source #
KeywordArgument | |
|
Instances
data BinaryOperator Source #
Instances
Attribute | |
|
Instances
Eq Attribute Source # | |
Ord Attribute Source # | |
Defined in TreeSitter.Python.AST | |
Show Attribute Source # | |
Generic Attribute Source # | |
Unmarshal Attribute Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Attribute | |
SymbolMatching Attribute Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Attribute -> Node -> Bool showFailure :: Proxy Attribute -> Node -> String | |
type Rep Attribute Source # | |
Defined in TreeSitter.Python.AST type Rep Attribute = D1 (MetaData "Attribute" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Attribute" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either PrimaryExpression Identifier]))) |
WithItem | |
|
Instances
Eq WithItem Source # | |
Ord WithItem Source # | |
Defined in TreeSitter.Python.AST | |
Show WithItem Source # | |
Generic WithItem Source # | |
Unmarshal WithItem Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m WithItem | |
SymbolMatching WithItem Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy WithItem -> Node -> Bool showFailure :: Proxy WithItem -> Node -> String | |
type Rep WithItem Source # | |
Defined in TreeSitter.Python.AST type Rep WithItem = D1 (MetaData "WithItem" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "WithItem" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Expression]))) |
data ReturnStatement Source #
Instances
data RaiseStatement Source #
Instances
data DeleteStatement Source #
Instances
data Assignment Source #
Assignment | |
|
Instances
data AugmentedAssignment Source #
Instances
data ExpressionStatement Source #
ExpressionStatement | |
|
Instances
data ExecStatement Source #
ExecStatement | |
|
Instances
data Parameters Source #
Instances
Chevron | |
|
Instances
Eq Chevron Source # | |
Ord Chevron Source # | |
Show Chevron Source # | |
Generic Chevron Source # | |
Unmarshal Chevron Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Chevron | |
SymbolMatching Chevron Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Chevron -> Node -> Bool showFailure :: Proxy Chevron -> Node -> String | |
type Rep Chevron Source # | |
Defined in TreeSitter.Python.AST type Rep Chevron = D1 (MetaData "Chevron" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Chevron" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Expression]))) |
data PrintStatement Source #
PrintStatement | |
|
Instances
data AssertStatement Source #
AssertStatement | |
|
Instances
data SimpleStatement Source #
Instances
Decorator | |
|
Instances
Eq Decorator Source # | |
Ord Decorator Source # | |
Defined in TreeSitter.Python.AST | |
Show Decorator Source # | |
Generic Decorator Source # | |
Unmarshal Decorator Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Decorator | |
SymbolMatching Decorator Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Decorator -> Node -> Bool showFailure :: Proxy Decorator -> Node -> String | |
type Rep Decorator Source # | |
Defined in TreeSitter.Python.AST type Rep Decorator = D1 (MetaData "Decorator" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Decorator" PrefixI True) (S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either ArgumentList DottedName]))) |
data ClassDefinition Source #
ClassDefinition | |
|
Instances
Block | |
|
Instances
Eq Block Source # | |
Ord Block Source # | |
Show Block Source # | |
Generic Block Source # | |
Unmarshal Block Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Block | |
SymbolMatching Block Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Block -> Node -> Bool showFailure :: Proxy Block -> Node -> String | |
type Rep Block Source # | |
Defined in TreeSitter.Python.AST type Rep Block = D1 (MetaData "Block" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Block" PrefixI True) (S1 (MetaSel (Just "statement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either CompoundStatement SimpleStatement]))) |
data CompoundStatement Source #
Instances
data WithStatement Source #
WithStatement | |
|
Instances
data WhileStatement Source #
WhileStatement | |
|
Instances
data ElseClause Source #
Instances
data TryStatement Source #
TryStatement | |
|
Instances
data FinallyClause Source #
FinallyClause | |
|
Instances
data ExceptClause Source #
ExceptClause | |
|
Instances
data IfStatement Source #
IfStatement | |
|
Instances
data ElifClause Source #
Instances
data FunctionDefinition Source #
FunctionDefinition | |
|
Instances
data ForStatement Source #
ForStatement | |
|
Instances
data DecoratedDefinition Source #
DecoratedDefinition | |
|
Instances
Module | |
|
Instances
Eq Module Source # | |
Ord Module Source # | |
Show Module Source # | |
Generic Module Source # | |
Unmarshal Module Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Module | |
SymbolMatching Module Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Module -> Node -> Bool showFailure :: Proxy Module -> Node -> String | |
type Rep Module Source # | |
Defined in TreeSitter.Python.AST type Rep Module = D1 (MetaData "Module" "TreeSitter.Python.AST" "tree-sitter-python-0.2.0.0-inplace" False) (C1 (MetaCons "Module" PrefixI True) (S1 (MetaSel (Just "statement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either CompoundStatement SimpleStatement]))) |
data AnonymousAwait Source #
Instances
Instances
Eq Comment Source # | |
Ord Comment Source # | |
Show Comment Source # | |
Generic Comment Source # | |
Unmarshal Comment Source # | |
Defined in TreeSitter.Python.AST unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Comment | |
SymbolMatching Comment Source # | |
Defined in TreeSitter.Python.AST symbolMatch :: Proxy Comment -> Node -> Bool showFailure :: Proxy Comment -> Node -> String | |
type Rep Comment Source # | |
Defined in TreeSitter.Python.AST |