Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
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 #
Instances
type AnonymousTry = Token "try" 29 Source #
Instances
Functor True Source # | |
Foldable True Source # | |
Defined in TreeSitter.Python.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.Python.AST symbolMatch :: Proxy True -> Node -> Bool showFailure :: Proxy True -> Node -> String | |
Unmarshal True Source # | |
Defined in TreeSitter.Python.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.Python.AST type Rep (True a) = D1 (MetaData "True" "TreeSitter.Python.AST" "tree-sitter-python-0.7.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.Python.AST type Rep1 True = D1 (MetaData "True" "TreeSitter.Python.AST" "tree-sitter-python-0.7.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 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 fold :: Monoid m => None m -> 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 symbolMatch :: Proxy None -> Node -> Bool showFailure :: Proxy None -> Node -> String | |
Unmarshal None Source # | |
Defined in TreeSitter.Python.AST unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (None a) | |
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.7.0.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.7.0.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 #
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 #
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 AnonymousFuture = 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 #
Yield | |
|
Instances
data WithStatement a Source #
Instances
WithItem | |
|
Instances
data WildcardImport a Source #
Instances
data WhileStatement a Source #
WhileStatement | |
|
Instances
Variables | |
|
Instances
data UnaryOperator a Source #
UnaryOperator | |
|
Instances
data TypedParameter a Source #
TypedParameter | |
|
Instances
data TypedDefaultParameter a Source #
TypedDefaultParameter | |
|
Instances
Type | |
|
Instances
Functor Type Source # | |
Foldable Type Source # | |
Defined in TreeSitter.Python.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.Python.AST symbolMatch :: Proxy Type -> Node -> Bool showFailure :: Proxy Type -> Node -> String | |
Unmarshal Type Source # | |
Defined in TreeSitter.Python.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.Python.AST type Rep (Type a) = D1 (MetaData "Type" "TreeSitter.Python.AST" "tree-sitter-python-0.7.0.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.7.0.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))) |
Tuple | |
|
Instances
data TryStatement a Source #
TryStatement | |
|
Instances
Subscript | |
|
Instances
String | |
|
Instances
Slice | |
|
Instances
data SetComprehension a Source #
SetComprehension | |
|
Instances
Set | |
|
Instances
Functor Set Source # | |
Foldable Set Source # | |
Defined in TreeSitter.Python.AST fold :: Monoid m => Set m -> 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 symbolMatch :: Proxy Set -> Node -> Bool showFailure :: Proxy Set -> Node -> String | |
Unmarshal Set Source # | |
Defined in TreeSitter.Python.AST unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Set a) | |
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.7.0.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.7.0.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 #
ReturnStatement | |
|
Instances
data RelativeImport a Source #
RelativeImport | |
|
Instances
data RaiseStatement a Source #
RaiseStatement | |
|
Instances
data PrintStatement a Source #
PrintStatement | |
|
Instances
data PassStatement a Source #
Instances
data ParenthesizedExpression a Source #
ParenthesizedExpression | |
|
Instances
data Parameters a Source #
Parameters | |
|
Instances
Pair | |
|
Instances
data NotOperator a Source #
NotOperator | |
|
Instances
data NonlocalStatement a Source #
NonlocalStatement | |
|
Instances
data NamedExpression a Source #
NamedExpression | |
|
Instances
Module | |
|
Instances
ListSplat | |
|
Instances
data ListComprehension a Source #
ListComprehension | |
|
Instances
List | |
|
Instances
data LambdaParameters a Source #
LambdaParameters | |
|
Instances
Lambda | |
|
Instances
data KeywordArgument a Source #
KeywordArgument | |
|
Instances
data Interpolation a Source #
Interpolation | |
|
Instances
data ImportStatement a Source #
ImportStatement | |
|
Instances
data ImportPrefix a Source #
Instances
data ImportFromStatement a Source #
ImportFromStatement | |
|
Instances
data IfStatement a Source #
IfStatement | |
|
Instances
IfClause | |
|
Instances
data GlobalStatement a Source #
GlobalStatement | |
|
Instances
data GeneratorExpression a Source #
GeneratorExpression | |
|
Instances
data FutureImportStatement a Source #
FutureImportStatement | |
|
Instances
data FunctionDefinition a Source #
FunctionDefinition | |
|
Instances
data FormatSpecifier a Source #
FormatSpecifier | |
|
Instances
data FormatExpression a Source #
FormatExpression | |
|
Instances
data ForStatement a Source #
ForStatement | |
|
Instances
data ForInClause a Source #
ForInClause | |
|
Instances
data FinallyClause a Source #
FinallyClause | |
|
Instances
data ExpressionStatement a Source #
ExpressionStatement | |
|
Instances
data ExpressionList a Source #
ExpressionList | |
|
Instances
data ExecStatement a Source #
ExecStatement | |
|
Instances
data ExceptClause a Source #
ExceptClause | |
|
Instances
data ElseClause a Source #
Instances
data ElifClause a Source #
ElifClause | |
|
Instances
data DottedName a Source #
DottedName | |
|
Instances
data DictionarySplat a Source #
DictionarySplat | |
|
Instances
data DictionaryComprehension a Source #
DictionaryComprehension | |
|
Instances
data Dictionary a Source #
Dictionary | |
|
Instances
data DeleteStatement a Source #
DeleteStatement | |
|
Instances
data DefaultParameter a Source #
DefaultParameter | |
|
Instances
Decorator | |
|
Instances
data DecoratedDefinition a Source #
DecoratedDefinition | |
|
Instances
data ContinueStatement a Source #
Instances
data ConditionalExpression a Source #
ConditionalExpression | |
|
Instances
data ConcatenatedString a Source #
ConcatenatedString | |
|
Instances
data ComparisonOperator a Source #
ComparisonOperator | |
|
Instances
data ClassDefinition a Source #
ClassDefinition | |
|
Instances
Chevron | |
|
Instances
Call | |
|
Instances
data BreakStatement a Source #
Instances
data BooleanOperator a Source #
BooleanOperator | |
|
Instances
Block | |
|
Instances
data BinaryOperator a Source #
Instances
Await | |
|
Instances
data AugmentedAssignment a Source #
Instances
Attribute | |
|
Instances
data Assignment a Source #
Assignment | |
|
Instances
data AssertStatement a Source #
AssertStatement | |
|
Instances
data ArgumentList a Source #
ArgumentList | |
|
Instances
data AliasedImport a Source #
AliasedImport | |
|
Instances
newtype SimpleStatement a Source #
Instances
newtype PrimaryExpression a Source #
PrimaryExpression ((:+:) ((:+:) ((:+:) ((:+:) Attribute BinaryOperator) ((:+:) Call ((:+:) ConcatenatedString Dictionary))) ((:+:) ((:+:) DictionaryComprehension ((:+:) Ellipsis False)) ((:+:) Float ((:+:) GeneratorExpression Identifier)))) ((:+:) ((:+:) ((:+:) Integer ((:+:) List ListComprehension)) ((:+:) None ((:+:) ParenthesizedExpression Set))) ((:+:) ((:+:) SetComprehension ((:+:) String Subscript)) ((:+:) True ((:+:) Tuple UnaryOperator)))) a) |
Instances
Parameter ((:+:) ((:+:) DefaultParameter ((:+:) DictionarySplat Identifier)) ((:+:) ((:+:) ListSplat Tuple) ((:+:) TypedDefaultParameter TypedParameter)) a) |
Instances
newtype Expression a Source #
Expression ((:+:) ((:+:) ((:+:) PrimaryExpression Await) ((:+:) BooleanOperator ComparisonOperator)) ((:+:) ((:+:) ConditionalExpression Lambda) ((:+:) NamedExpression NotOperator)) a) |
Instances
newtype CompoundStatement a Source #
CompoundStatement ((:+:) ((:+:) ((:+:) ClassDefinition DecoratedDefinition) ((:+:) ForStatement FunctionDefinition)) ((:+:) ((:+:) IfStatement TryStatement) ((:+:) WhileStatement WithStatement)) a) |