| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
TreeSitter.Python.AST
Documentation
debugSymbolNames :: [String] Source #
type AnonymousTilde = Token "~" 54 Source #
type AnonymousRBrace = Token "}" 82 Source #
type AnonymousPipeEqual = Token "|=" 76 Source #
type AnonymousPipe = Token "|" 50 Source #
type AnonymousLBrace = Token "{" 81 Source #
type AnonymousYield = Token "yield" 77 Source #
type AnonymousWith = Token "with" 32 Source #
type AnonymousWhile = Token "while" 28 Source #
data TypeConversion a Source #
Constructors
| TypeConversion | |
Instances
type AnonymousTry = Token "try" 29 Source #
Instances
| Functor True Source # | |
| Foldable True Source # | |
Defined in TreeSitter.Python.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.Python.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.Python.AST type Rep (True a) = D1 ('MetaData "True" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.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.Python.AST type Rep1 True = D1 ('MetaData "True" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.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 AnonymousReturn = Token "return" 15 Source #
type AnonymousRaise = Token "raise" 17 Source #
type AnonymousPrint = Token "print" 11 Source #
type AnonymousPass = Token "pass" 18 Source #
type AnonymousOr = Token "or" 44 Source #
type AnonymousNot = Token "not" 42 Source #
type AnonymousNonlocal = Token "nonlocal" 38 Source #
Instances
| Functor None Source # | |
| Foldable None Source # | |
Defined in TreeSitter.Python.AST Methods fold :: Monoid m => None m -> m # foldMap :: Monoid m => (a -> m) -> None a -> m # foldMap' :: Monoid m => (a -> m) -> None a -> m # foldr :: (a -> b -> b) -> b -> None a -> b # foldr' :: (a -> b -> b) -> b -> None a -> b # foldl :: (b -> a -> b) -> b -> None a -> b # foldl' :: (b -> a -> b) -> b -> None a -> b # foldr1 :: (a -> a -> a) -> None a -> a # foldl1 :: (a -> a -> a) -> None a -> a # elem :: Eq a => a -> None a -> Bool # maximum :: Ord a => None a -> a # | |
| Traversable None Source # | |
| SymbolMatching None Source # | |
Defined in TreeSitter.Python.AST | |
| Unmarshal None Source # | |
| Eq a => Eq (None a) Source # | |
| Ord a => Ord (None a) Source # | |
| Show a => Show (None a) Source # | |
| Generic (None a) Source # | |
| Generic1 None Source # | |
| type Rep (None a) Source # | |
Defined in TreeSitter.Python.AST type Rep (None a) = D1 ('MetaData "None" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "None" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
| type Rep1 None Source # | |
Defined in TreeSitter.Python.AST type Rep1 None = D1 ('MetaData "None" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "None" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
type AnonymousLambda = Token "lambda" 63 Source #
type AnonymousIs = Token "is" 62 Source #
Instances
type AnonymousIn = Token "in" 27 Source #
type AnonymousImport = Token "import" 2 Source #
type AnonymousIf = Token "if" 21 Source #
data Identifier a Source #
Constructors
| Identifier | |
Instances
type AnonymousGlobal = Token "global" 37 Source #
type AnonymousFrom = Token "from" 4 Source #
type AnonymousFor = Token "for" 26 Source #
Instances
type AnonymousFinally = Token "finally" 31 Source #
Instances
type AnonymousExec = Token "exec" 39 Source #
type AnonymousExcept = Token "except" 30 Source #
data EscapeSequence a Source #
Constructors
| EscapeSequence | |
Instances
type AnonymousElse = Token "else" 24 Source #
Instances
type AnonymousElif = Token "elif" 23 Source #
type AnonymousDel = Token "del" 16 Source #
type AnonymousDef = Token "def" 33 Source #
type AnonymousContinue = Token "continue" 20 Source #
type AnonymousClass = Token "class" 40 Source #
type AnonymousBreak = Token "break" 19 Source #
type AnonymousAwait = Token "await" 92 Source #
type AnonymousAsync = Token "async" 25 Source #
type AnonymousAssert = Token "assert" 13 Source #
type AnonymousAs = Token "as" 9 Source #
type AnonymousAnd = Token "and" 43 Source #
type AnonymousUnderscorefutureUnderscore = Token "__future__" 5 Source #
type AnonymousCaretEqual = Token "^=" 75 Source #
type AnonymousCaret = Token "^" 52 Source #
type AnonymousRBracket = Token "]" 79 Source #
type AnonymousLBracket = Token "[" 78 Source #
type AnonymousAtEqual = Token "@=" 68 Source #
type AnonymousAt = Token "@" 41 Source #
type AnonymousRAngleRAngleEqual = Token ">>=" 72 Source #
type AnonymousRAngleRAngle = Token ">>" 12 Source #
type AnonymousRAngleEqual = Token ">=" 59 Source #
type AnonymousRAngle = Token ">" 60 Source #
type AnonymousEqualEqual = Token "==" 57 Source #
type AnonymousEqual = Token "=" 35 Source #
type AnonymousLAngleRAngle = Token "<>" 61 Source #
type AnonymousLAngleEqual = Token "<=" 56 Source #
type AnonymousLAngleLAngleEqual = Token "<<=" 73 Source #
type AnonymousLAngleLAngle = Token "<<" 53 Source #
type AnonymousLAngle = Token "<" 55 Source #
type AnonymousColonEqual = Token ":=" 14 Source #
type AnonymousColon = Token ":" 22 Source #
type AnonymousSlashEqual = Token "/=" 67 Source #
type AnonymousSlashSlashEqual = Token "//=" 69 Source #
type AnonymousSlashSlash = Token "//" 49 Source #
type AnonymousSlash = Token "/" 47 Source #
type AnonymousDot = Token "." 3 Source #
type AnonymousMinusRAngle = Token "->" 34 Source #
type AnonymousMinusEqual = Token "-=" 65 Source #
type AnonymousMinus = Token "-" 46 Source #
type AnonymousComma = Token "," 8 Source #
type AnonymousPlusEqual = Token "+=" 64 Source #
type AnonymousPlus = Token "+" 45 Source #
type AnonymousStarEqual = Token "*=" 66 Source #
type AnonymousStarStarEqual = Token "**=" 71 Source #
type AnonymousStarStar = Token "**" 36 Source #
type AnonymousStar = Token "*" 10 Source #
type AnonymousRParen = Token ")" 7 Source #
type AnonymousLParen = Token "(" 6 Source #
type AnonymousAmpersandEqual = Token "&=" 74 Source #
type AnonymousAmpersand = Token "&" 51 Source #
type AnonymousPercentEqual = Token "%=" 70 Source #
type AnonymousPercent = Token "%" 48 Source #
type AnonymousBangEqual = Token "!=" 58 Source #
Constructors
| Yield | |
Fields
| |
Instances
data WithStatement a Source #
Constructors
| WithStatement | |
Instances
Constructors
| WithItem | |
Fields
| |
Instances
data WildcardImport a Source #
Constructors
| WildcardImport | |
Instances
data WhileStatement a Source #
Constructors
| WhileStatement | |
Fields
| |
Instances
Constructors
| Variables | |
Fields
| |
Instances
data UnaryOperator a Source #
Constructors
| UnaryOperator | |
Fields
| |
Instances
data TypedParameter a Source #
Constructors
| TypedParameter | |
Fields
| |
Instances
data TypedDefaultParameter a Source #
Constructors
| TypedDefaultParameter | |
Fields
| |
Instances
Constructors
| Type | |
Fields
| |
Instances
| Functor Type Source # | |
| Foldable Type Source # | |
Defined in TreeSitter.Python.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.Python.AST | |
| Unmarshal Type Source # | |
| 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.Python.AST type Rep (Type a) = D1 ('MetaData "Type" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "Type" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) | |
| type Rep1 Type Source # | |
Defined in TreeSitter.Python.AST type Rep1 Type = D1 ('MetaData "Type" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "Type" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Expression))) | |
Constructors
| Tuple | |
Fields
| |
Instances
data TryStatement a Source #
Constructors
| TryStatement | |
Fields
| |
Instances
Constructors
| Subscript | |
Fields
| |
Instances
Constructors
| String | |
Fields
| |
Instances
Constructors
| Slice | |
Fields
| |
Instances
data SetComprehension a Source #
Constructors
| SetComprehension | |
Fields
| |
Instances
Constructors
| Set | |
Fields
| |
Instances
| Functor Set Source # | |
| Foldable Set Source # | |
Defined in TreeSitter.Python.AST Methods fold :: Monoid m => Set m -> m # foldMap :: Monoid m => (a -> m) -> Set a -> m # foldMap' :: Monoid m => (a -> m) -> Set a -> m # foldr :: (a -> b -> b) -> b -> Set a -> b # foldr' :: (a -> b -> b) -> b -> Set a -> b # foldl :: (b -> a -> b) -> b -> Set a -> b # foldl' :: (b -> a -> b) -> b -> Set a -> b # foldr1 :: (a -> a -> a) -> Set a -> a # foldl1 :: (a -> a -> a) -> Set a -> a # elem :: Eq a => a -> Set a -> Bool # maximum :: Ord a => Set a -> a # | |
| Traversable Set Source # | |
| SymbolMatching Set Source # | |
Defined in TreeSitter.Python.AST | |
| Unmarshal Set Source # | |
| Eq a => Eq (Set a) Source # | |
| Ord a => Ord (Set a) Source # | |
| Show a => Show (Set a) Source # | |
| Generic (Set a) Source # | |
| Generic1 Set Source # | |
| type Rep (Set a) Source # | |
Defined in TreeSitter.Python.AST type Rep (Set a) = D1 ('MetaData "Set" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "Set" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty ((Expression :+: ListSplat) a))))) | |
| type Rep1 Set Source # | |
Defined in TreeSitter.Python.AST type Rep1 Set = D1 ('MetaData "Set" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "Set" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (NonEmpty :.: Rec1 (Expression :+: ListSplat)))) | |
data ReturnStatement a Source #
Constructors
| ReturnStatement | |
Fields
| |
Instances
data RelativeImport a Source #
Constructors
| RelativeImport | |
Fields
| |
Instances
data RaiseStatement a Source #
Constructors
| RaiseStatement | |
Fields
| |
Instances
data PrintStatement a Source #
Constructors
| PrintStatement | |
Fields
| |
Instances
data PassStatement a Source #
Constructors
| PassStatement | |
Instances
data ParenthesizedExpression a Source #
Constructors
| ParenthesizedExpression | |
Fields
| |
Instances
data Parameters a Source #
Constructors
| Parameters | |
Fields
| |
Instances
Constructors
| Pair | |
Fields
| |
Instances
data NotOperator a Source #
Constructors
| NotOperator | |
Fields
| |
Instances
data NonlocalStatement a Source #
Constructors
| NonlocalStatement | |
Fields
| |
Instances
data NamedExpression a Source #
Constructors
| NamedExpression | |
Fields
| |
Instances
Constructors
| Module | |
Fields
| |
Instances
Constructors
| ListSplat | |
Fields
| |
Instances
data ListComprehension a Source #
Constructors
| ListComprehension | |
Fields
| |
Instances
Constructors
| List | |
Fields
| |
Instances
| Functor List Source # | |
| Foldable List Source # | |
Defined in TreeSitter.Python.AST Methods fold :: Monoid m => List m -> m # foldMap :: Monoid m => (a -> m) -> List a -> m # foldMap' :: Monoid m => (a -> m) -> List a -> m # foldr :: (a -> b -> b) -> b -> List a -> b # foldr' :: (a -> b -> b) -> b -> List a -> b # foldl :: (b -> a -> b) -> b -> List a -> b # foldl' :: (b -> a -> b) -> b -> List a -> b # foldr1 :: (a -> a -> a) -> List a -> a # foldl1 :: (a -> a -> a) -> List a -> a # elem :: Eq a => a -> List a -> Bool # maximum :: Ord a => List a -> a # | |
| Traversable List Source # | |
| SymbolMatching List Source # | |
Defined in TreeSitter.Python.AST | |
| Unmarshal List Source # | |
| Eq a => Eq (List a) Source # | |
| Ord a => Ord (List a) Source # | |
| Show a => Show (List a) Source # | |
| Generic (List a) Source # | |
| Generic1 List Source # | |
| type Rep (List a) Source # | |
Defined in TreeSitter.Python.AST type Rep (List a) = D1 ('MetaData "List" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "List" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Expression :+: ListSplat) a]))) | |
| type Rep1 List Source # | |
Defined in TreeSitter.Python.AST type Rep1 List = D1 ('MetaData "List" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "List" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 (Expression :+: ListSplat)))) | |
data LambdaParameters a Source #
Constructors
| LambdaParameters | |
Fields
| |
Instances
Constructors
| Lambda | |
Fields
| |
Instances
data KeywordArgument a Source #
Constructors
| KeywordArgument | |
Fields
| |
Instances
data Interpolation a Source #
Constructors
| Interpolation | |
Fields
| |
Instances
data ImportStatement a Source #
Constructors
| ImportStatement | |
Fields
| |
Instances
data ImportPrefix a Source #
Constructors
| ImportPrefix | |
Instances
data ImportFromStatement a Source #
Constructors
| ImportFromStatement | |
Fields
| |
Instances
data IfStatement a Source #
Constructors
| IfStatement | |
Fields
| |
Instances
Constructors
| IfClause | |
Fields
| |
Instances
data GlobalStatement a Source #
Constructors
| GlobalStatement | |
Fields
| |
Instances
data GeneratorExpression a Source #
Constructors
| GeneratorExpression | |
Fields
| |
Instances
data FutureImportStatement a Source #
Constructors
| FutureImportStatement | |
Fields
| |
Instances
data FunctionDefinition a Source #
Constructors
| FunctionDefinition | |
Fields
| |
Instances
data FormatSpecifier a Source #
Constructors
| FormatSpecifier | |
Fields
| |
Instances
data FormatExpression a Source #
Constructors
| FormatExpression | |
Fields
| |
Instances
data ForStatement a Source #
Constructors
| ForStatement | |
Fields
| |
Instances
data ForInClause a Source #
Constructors
| ForInClause | |
Fields
| |
Instances
data FinallyClause a Source #
Constructors
| FinallyClause | |
Fields
| |
Instances
data ExpressionStatement a Source #
Constructors
| ExpressionStatement | |
Fields
| |
Instances
data ExpressionList a Source #
Constructors
| ExpressionList | |
Fields
| |
Instances
data ExecStatement a Source #
Constructors
| ExecStatement | |
Fields
| |
Instances
data ExceptClause a Source #
Constructors
| ExceptClause | |
Fields
| |
Instances
data ElseClause a Source #
Constructors
| ElseClause | |
Instances
data ElifClause a Source #
Constructors
| ElifClause | |
Fields
| |
Instances
data DottedName a Source #
Constructors
| DottedName | |
Fields
| |
Instances
data DictionarySplat a Source #
Constructors
| DictionarySplat | |
Fields
| |
Instances
data DictionaryComprehension a Source #
Constructors
| DictionaryComprehension | |
Fields
| |
Instances
data Dictionary a Source #
Constructors
| Dictionary | |
Fields
| |
Instances
data DeleteStatement a Source #
Constructors
| DeleteStatement | |
Fields
| |
Instances
data DefaultParameter a Source #
Constructors
| DefaultParameter | |
Fields
| |
Instances
Constructors
| Decorator | |
Fields
| |
Instances
data DecoratedDefinition a Source #
Constructors
| DecoratedDefinition | |
Fields
| |
Instances
data ContinueStatement a Source #
Constructors
| ContinueStatement | |
Instances
data ConditionalExpression a Source #
Constructors
| ConditionalExpression | |
Fields
| |
Instances
data ConcatenatedString a Source #
Constructors
| ConcatenatedString | |
Fields
| |
Instances
data ComparisonOperator a Source #
Constructors
| ComparisonOperator | |
Fields
| |
Instances
data ClassDefinition a Source #
Constructors
| ClassDefinition | |
Fields
| |
Instances
Constructors
| Chevron | |
Fields
| |
Instances
Constructors
| Call | |
Fields
| |
Instances
data BreakStatement a Source #
Constructors
| BreakStatement | |
Instances
data BooleanOperator a Source #
Constructors
| BooleanOperator | |
Fields
| |
Instances
Constructors
| Block | |
Fields
| |
Instances
data BinaryOperator a Source #
Constructors
| BinaryOperator | |
Fields
| |
Instances
Constructors
| Await | |
Fields
| |
Instances
data AugmentedAssignment a Source #
Constructors
Instances
Constructors
| Attribute | |
Fields
| |
Instances
data Assignment a Source #
Constructors
| Assignment | |
Fields
| |
Instances
data AssertStatement a Source #
Constructors
| AssertStatement | |
Fields
| |
Instances
data ArgumentList a Source #
Constructors
| ArgumentList | |
Fields
| |
Instances
data AliasedImport a Source #
Constructors
| AliasedImport | |
Fields
| |
Instances
newtype SimpleStatement a Source #
Constructors
Instances
newtype PrimaryExpression a Source #
Constructors
| PrimaryExpression | |
Fields
| |
Instances
Constructors
| Parameter | |
Fields | |
Instances
newtype Expression a Source #
Constructors
| Expression | |
Fields | |
Instances
newtype CompoundStatement a Source #
Constructors
| CompoundStatement | |