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