tree-sitter-python-0.4.0.0: Tree-sitter grammar/parser for Python

Safe HaskellNone
LanguageHaskell2010

TreeSitter.Python.AST

Documentation

data BreakStatement a Source #

Constructors

BreakStatement 

Fields

Instances
Eq a => Eq (BreakStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (BreakStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (BreakStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (BreakStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (BreakStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (BreakStatement a) Source # 
Instance details

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 (BreakStatement a)

SymbolMatching (BreakStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (BreakStatement a) -> Node -> Bool

showFailure :: Proxy (BreakStatement a) -> Node -> String

type Rep (BreakStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (BreakStatement a) = D1 (MetaData "BreakStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "BreakStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data ContinueStatement a Source #

Constructors

ContinueStatement 

Fields

Instances
Eq a => Eq (ContinueStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ContinueStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ContinueStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ContinueStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ContinueStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (ContinueStatement a) Source # 
Instance details

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 (ContinueStatement a)

SymbolMatching (ContinueStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ContinueStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ContinueStatement a) = D1 (MetaData "ContinueStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ContinueStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data ImportPrefix a Source #

Constructors

ImportPrefix 

Fields

Instances
Eq a => Eq (ImportPrefix a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ImportPrefix a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ImportPrefix a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ImportPrefix a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ImportPrefix a) :: Type -> Type #

Methods

from :: ImportPrefix a -> Rep (ImportPrefix a) x #

to :: Rep (ImportPrefix a) x -> ImportPrefix a #

Unmarshal a => Unmarshal (ImportPrefix a) Source # 
Instance details

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 (ImportPrefix a)

SymbolMatching (ImportPrefix a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (ImportPrefix a) -> Node -> Bool

showFailure :: Proxy (ImportPrefix a) -> Node -> String

type Rep (ImportPrefix a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ImportPrefix a) = D1 (MetaData "ImportPrefix" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ImportPrefix" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data PassStatement a Source #

Constructors

PassStatement 

Fields

Instances
Eq a => Eq (PassStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (PassStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (PassStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (PassStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (PassStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (PassStatement a) Source # 
Instance details

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 (PassStatement a)

SymbolMatching (PassStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (PassStatement a) -> Node -> Bool

showFailure :: Proxy (PassStatement a) -> Node -> String

type Rep (PassStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (PassStatement a) = D1 (MetaData "PassStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "PassStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data WildcardImport a Source #

Constructors

WildcardImport 

Fields

Instances
Eq a => Eq (WildcardImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (WildcardImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (WildcardImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (WildcardImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (WildcardImport a) :: Type -> Type #

Unmarshal a => Unmarshal (WildcardImport a) Source # 
Instance details

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 (WildcardImport a)

SymbolMatching (WildcardImport a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (WildcardImport a) -> Node -> Bool

showFailure :: Proxy (WildcardImport a) -> Node -> String

type Rep (WildcardImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (WildcardImport a) = D1 (MetaData "WildcardImport" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "WildcardImport" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype AnonymousImport a Source #

Constructors

AnonymousImport 

Fields

Instances
Eq a => Eq (AnonymousImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousImport a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousImport a) Source # 
Instance details

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 (AnonymousImport a)

SymbolMatching (AnonymousImport a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousImport a) -> Node -> Bool

showFailure :: Proxy (AnonymousImport a) -> Node -> String

type Rep (AnonymousImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousImport a) = D1 (MetaData "AnonymousImport" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousImport" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousDot a Source #

Constructors

AnonymousDot 

Fields

Instances
Eq a => Eq (AnonymousDot a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousDot a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousDot a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousDot a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousDot a) :: Type -> Type #

Methods

from :: AnonymousDot a -> Rep (AnonymousDot a) x #

to :: Rep (AnonymousDot a) x -> AnonymousDot a #

Unmarshal a => Unmarshal (AnonymousDot a) Source # 
Instance details

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 (AnonymousDot a)

SymbolMatching (AnonymousDot a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousDot a) -> Node -> Bool

showFailure :: Proxy (AnonymousDot a) -> Node -> String

type Rep (AnonymousDot a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousDot a) = D1 (MetaData "AnonymousDot" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousDot" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousFrom a Source #

Constructors

AnonymousFrom 

Fields

Instances
Eq a => Eq (AnonymousFrom a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousFrom a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousFrom a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousFrom a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousFrom a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousFrom a) Source # 
Instance details

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 (AnonymousFrom a)

SymbolMatching (AnonymousFrom a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousFrom a) -> Node -> Bool

showFailure :: Proxy (AnonymousFrom a) -> Node -> String

type Rep (AnonymousFrom a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousFrom a) = D1 (MetaData "AnonymousFrom" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousFrom" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousFuture a Source #

Constructors

AnonymousFuture 

Fields

Instances
Eq a => Eq (AnonymousFuture a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousFuture a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousFuture a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousFuture a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousFuture a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousFuture a) Source # 
Instance details

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 (AnonymousFuture a)

SymbolMatching (AnonymousFuture a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousFuture a) -> Node -> Bool

showFailure :: Proxy (AnonymousFuture a) -> Node -> String

type Rep (AnonymousFuture a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousFuture a) = D1 (MetaData "AnonymousFuture" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousFuture" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousLParen a Source #

Constructors

AnonymousLParen 

Fields

Instances
Eq a => Eq (AnonymousLParen a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousLParen a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousLParen a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousLParen a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousLParen a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousLParen a) Source # 
Instance details

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 (AnonymousLParen a)

SymbolMatching (AnonymousLParen a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousLParen a) -> Node -> Bool

showFailure :: Proxy (AnonymousLParen a) -> Node -> String

type Rep (AnonymousLParen a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLParen a) = D1 (MetaData "AnonymousLParen" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousLParen" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousRParen a Source #

Constructors

AnonymousRParen 

Fields

Instances
Eq a => Eq (AnonymousRParen a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousRParen a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousRParen a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousRParen a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousRParen a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousRParen a) Source # 
Instance details

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 (AnonymousRParen a)

SymbolMatching (AnonymousRParen a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousRParen a) -> Node -> Bool

showFailure :: Proxy (AnonymousRParen a) -> Node -> String

type Rep (AnonymousRParen a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousRParen a) = D1 (MetaData "AnonymousRParen" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousRParen" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousComma a Source #

Constructors

AnonymousComma 

Fields

Instances
Eq a => Eq (AnonymousComma a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousComma a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousComma a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousComma a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousComma a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousComma a) Source # 
Instance details

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 (AnonymousComma a)

SymbolMatching (AnonymousComma a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousComma a) -> Node -> Bool

showFailure :: Proxy (AnonymousComma a) -> Node -> String

type Rep (AnonymousComma a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousComma a) = D1 (MetaData "AnonymousComma" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousComma" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousAs a Source #

Constructors

AnonymousAs 

Fields

Instances
Eq a => Eq (AnonymousAs a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousAs a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousAs a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousAs a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousAs a) :: Type -> Type #

Methods

from :: AnonymousAs a -> Rep (AnonymousAs a) x #

to :: Rep (AnonymousAs a) x -> AnonymousAs a #

Unmarshal a => Unmarshal (AnonymousAs a) Source # 
Instance details

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 (AnonymousAs a)

SymbolMatching (AnonymousAs a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousAs a) -> Node -> Bool

showFailure :: Proxy (AnonymousAs a) -> Node -> String

type Rep (AnonymousAs a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousAs a) = D1 (MetaData "AnonymousAs" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousAs" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousStar a Source #

Constructors

AnonymousStar 

Fields

Instances
Eq a => Eq (AnonymousStar a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousStar a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousStar a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousStar a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousStar a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousStar a) Source # 
Instance details

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 (AnonymousStar a)

SymbolMatching (AnonymousStar a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousStar a) -> Node -> Bool

showFailure :: Proxy (AnonymousStar a) -> Node -> String

type Rep (AnonymousStar a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousStar a) = D1 (MetaData "AnonymousStar" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousStar" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousPrint a Source #

Constructors

AnonymousPrint 

Fields

Instances
Eq a => Eq (AnonymousPrint a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousPrint a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousPrint a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousPrint a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousPrint a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousPrint a) Source # 
Instance details

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 (AnonymousPrint a)

SymbolMatching (AnonymousPrint a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousPrint a) -> Node -> Bool

showFailure :: Proxy (AnonymousPrint a) -> Node -> String

type Rep (AnonymousPrint a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousPrint a) = D1 (MetaData "AnonymousPrint" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousPrint" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousRAngleRAngle a Source #

Constructors

AnonymousRAngleRAngle 

Fields

Instances
Eq a => Eq (AnonymousRAngleRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousRAngleRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousRAngleRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousRAngleRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousRAngleRAngle a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousRAngleRAngle a) Source # 
Instance details

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 (AnonymousRAngleRAngle a)

SymbolMatching (AnonymousRAngleRAngle a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousRAngleRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousRAngleRAngle a) = D1 (MetaData "AnonymousRAngleRAngle" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousRAngleRAngle" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousAssert a Source #

Constructors

AnonymousAssert 

Fields

Instances
Eq a => Eq (AnonymousAssert a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousAssert a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousAssert a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousAssert a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousAssert a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousAssert a) Source # 
Instance details

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 (AnonymousAssert a)

SymbolMatching (AnonymousAssert a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousAssert a) -> Node -> Bool

showFailure :: Proxy (AnonymousAssert a) -> Node -> String

type Rep (AnonymousAssert a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousAssert a) = D1 (MetaData "AnonymousAssert" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousAssert" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousColonEqual a Source #

Constructors

AnonymousColonEqual 

Fields

Instances
Eq a => Eq (AnonymousColonEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousColonEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousColonEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousColonEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousColonEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousColonEqual a) Source # 
Instance details

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 (AnonymousColonEqual a)

SymbolMatching (AnonymousColonEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousColonEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousColonEqual a) = D1 (MetaData "AnonymousColonEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousColonEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousReturn a Source #

Constructors

AnonymousReturn 

Fields

Instances
Eq a => Eq (AnonymousReturn a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousReturn a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousReturn a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousReturn a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousReturn a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousReturn a) Source # 
Instance details

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 (AnonymousReturn a)

SymbolMatching (AnonymousReturn a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousReturn a) -> Node -> Bool

showFailure :: Proxy (AnonymousReturn a) -> Node -> String

type Rep (AnonymousReturn a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousReturn a) = D1 (MetaData "AnonymousReturn" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousReturn" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousDel a Source #

Constructors

AnonymousDel 

Fields

Instances
Eq a => Eq (AnonymousDel a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousDel a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousDel a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousDel a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousDel a) :: Type -> Type #

Methods

from :: AnonymousDel a -> Rep (AnonymousDel a) x #

to :: Rep (AnonymousDel a) x -> AnonymousDel a #

Unmarshal a => Unmarshal (AnonymousDel a) Source # 
Instance details

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 (AnonymousDel a)

SymbolMatching (AnonymousDel a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousDel a) -> Node -> Bool

showFailure :: Proxy (AnonymousDel a) -> Node -> String

type Rep (AnonymousDel a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousDel a) = D1 (MetaData "AnonymousDel" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousDel" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousRaise a Source #

Constructors

AnonymousRaise 

Fields

Instances
Eq a => Eq (AnonymousRaise a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousRaise a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousRaise a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousRaise a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousRaise a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousRaise a) Source # 
Instance details

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 (AnonymousRaise a)

SymbolMatching (AnonymousRaise a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousRaise a) -> Node -> Bool

showFailure :: Proxy (AnonymousRaise a) -> Node -> String

type Rep (AnonymousRaise a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousRaise a) = D1 (MetaData "AnonymousRaise" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousRaise" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousPass a Source #

Constructors

AnonymousPass 

Fields

Instances
Eq a => Eq (AnonymousPass a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousPass a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousPass a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousPass a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousPass a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousPass a) Source # 
Instance details

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 (AnonymousPass a)

SymbolMatching (AnonymousPass a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousPass a) -> Node -> Bool

showFailure :: Proxy (AnonymousPass a) -> Node -> String

type Rep (AnonymousPass a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousPass a) = D1 (MetaData "AnonymousPass" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousPass" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousBreak a Source #

Constructors

AnonymousBreak 

Fields

Instances
Eq a => Eq (AnonymousBreak a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousBreak a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousBreak a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousBreak a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousBreak a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousBreak a) Source # 
Instance details

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 (AnonymousBreak a)

SymbolMatching (AnonymousBreak a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousBreak a) -> Node -> Bool

showFailure :: Proxy (AnonymousBreak a) -> Node -> String

type Rep (AnonymousBreak a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousBreak a) = D1 (MetaData "AnonymousBreak" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousBreak" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousContinue a Source #

Constructors

AnonymousContinue 

Fields

Instances
Eq a => Eq (AnonymousContinue a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousContinue a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousContinue a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousContinue a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousContinue a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousContinue a) Source # 
Instance details

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 (AnonymousContinue a)

SymbolMatching (AnonymousContinue a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousContinue a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousContinue a) = D1 (MetaData "AnonymousContinue" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousContinue" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousIf a Source #

Constructors

AnonymousIf 

Fields

Instances
Eq a => Eq (AnonymousIf a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousIf a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousIf a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousIf a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousIf a) :: Type -> Type #

Methods

from :: AnonymousIf a -> Rep (AnonymousIf a) x #

to :: Rep (AnonymousIf a) x -> AnonymousIf a #

Unmarshal a => Unmarshal (AnonymousIf a) Source # 
Instance details

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 (AnonymousIf a)

SymbolMatching (AnonymousIf a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousIf a) -> Node -> Bool

showFailure :: Proxy (AnonymousIf a) -> Node -> String

type Rep (AnonymousIf a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousIf a) = D1 (MetaData "AnonymousIf" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousIf" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousColon a Source #

Constructors

AnonymousColon 

Fields

Instances
Eq a => Eq (AnonymousColon a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousColon a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousColon a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousColon a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousColon a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousColon a) Source # 
Instance details

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 (AnonymousColon a)

SymbolMatching (AnonymousColon a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousColon a) -> Node -> Bool

showFailure :: Proxy (AnonymousColon a) -> Node -> String

type Rep (AnonymousColon a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousColon a) = D1 (MetaData "AnonymousColon" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousColon" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousElif a Source #

Constructors

AnonymousElif 

Fields

Instances
Eq a => Eq (AnonymousElif a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousElif a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousElif a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousElif a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousElif a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousElif a) Source # 
Instance details

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 (AnonymousElif a)

SymbolMatching (AnonymousElif a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousElif a) -> Node -> Bool

showFailure :: Proxy (AnonymousElif a) -> Node -> String

type Rep (AnonymousElif a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousElif a) = D1 (MetaData "AnonymousElif" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousElif" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousElse a Source #

Constructors

AnonymousElse 

Fields

Instances
Eq a => Eq (AnonymousElse a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousElse a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousElse a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousElse a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousElse a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousElse a) Source # 
Instance details

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 (AnonymousElse a)

SymbolMatching (AnonymousElse a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousElse a) -> Node -> Bool

showFailure :: Proxy (AnonymousElse a) -> Node -> String

type Rep (AnonymousElse a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousElse a) = D1 (MetaData "AnonymousElse" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousElse" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousAsync a Source #

Constructors

AnonymousAsync 

Fields

Instances
Eq a => Eq (AnonymousAsync a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousAsync a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousAsync a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousAsync a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousAsync a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousAsync a) Source # 
Instance details

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 (AnonymousAsync a)

SymbolMatching (AnonymousAsync a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousAsync a) -> Node -> Bool

showFailure :: Proxy (AnonymousAsync a) -> Node -> String

type Rep (AnonymousAsync a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousAsync a) = D1 (MetaData "AnonymousAsync" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousAsync" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousFor a Source #

Constructors

AnonymousFor 

Fields

Instances
Eq a => Eq (AnonymousFor a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousFor a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousFor a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousFor a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousFor a) :: Type -> Type #

Methods

from :: AnonymousFor a -> Rep (AnonymousFor a) x #

to :: Rep (AnonymousFor a) x -> AnonymousFor a #

Unmarshal a => Unmarshal (AnonymousFor a) Source # 
Instance details

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 (AnonymousFor a)

SymbolMatching (AnonymousFor a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousFor a) -> Node -> Bool

showFailure :: Proxy (AnonymousFor a) -> Node -> String

type Rep (AnonymousFor a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousFor a) = D1 (MetaData "AnonymousFor" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousFor" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousIn a Source #

Constructors

AnonymousIn 

Fields

Instances
Eq a => Eq (AnonymousIn a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousIn a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousIn a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousIn a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousIn a) :: Type -> Type #

Methods

from :: AnonymousIn a -> Rep (AnonymousIn a) x #

to :: Rep (AnonymousIn a) x -> AnonymousIn a #

Unmarshal a => Unmarshal (AnonymousIn a) Source # 
Instance details

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 (AnonymousIn a)

SymbolMatching (AnonymousIn a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousIn a) -> Node -> Bool

showFailure :: Proxy (AnonymousIn a) -> Node -> String

type Rep (AnonymousIn a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousIn a) = D1 (MetaData "AnonymousIn" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousIn" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousWhile a Source #

Constructors

AnonymousWhile 

Fields

Instances
Eq a => Eq (AnonymousWhile a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousWhile a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousWhile a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousWhile a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousWhile a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousWhile a) Source # 
Instance details

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 (AnonymousWhile a)

SymbolMatching (AnonymousWhile a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousWhile a) -> Node -> Bool

showFailure :: Proxy (AnonymousWhile a) -> Node -> String

type Rep (AnonymousWhile a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousWhile a) = D1 (MetaData "AnonymousWhile" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousWhile" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousTry a Source #

Constructors

AnonymousTry 

Fields

Instances
Eq a => Eq (AnonymousTry a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousTry a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousTry a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousTry a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousTry a) :: Type -> Type #

Methods

from :: AnonymousTry a -> Rep (AnonymousTry a) x #

to :: Rep (AnonymousTry a) x -> AnonymousTry a #

Unmarshal a => Unmarshal (AnonymousTry a) Source # 
Instance details

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 (AnonymousTry a)

SymbolMatching (AnonymousTry a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousTry a) -> Node -> Bool

showFailure :: Proxy (AnonymousTry a) -> Node -> String

type Rep (AnonymousTry a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousTry a) = D1 (MetaData "AnonymousTry" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousTry" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousExcept a Source #

Constructors

AnonymousExcept 

Fields

Instances
Eq a => Eq (AnonymousExcept a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousExcept a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousExcept a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousExcept a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousExcept a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousExcept a) Source # 
Instance details

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 (AnonymousExcept a)

SymbolMatching (AnonymousExcept a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousExcept a) -> Node -> Bool

showFailure :: Proxy (AnonymousExcept a) -> Node -> String

type Rep (AnonymousExcept a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousExcept a) = D1 (MetaData "AnonymousExcept" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousExcept" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousFinally a Source #

Constructors

AnonymousFinally 

Fields

Instances
Eq a => Eq (AnonymousFinally a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousFinally a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousFinally a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousFinally a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousFinally a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousFinally a) Source # 
Instance details

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 (AnonymousFinally a)

SymbolMatching (AnonymousFinally a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousFinally a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousFinally a) = D1 (MetaData "AnonymousFinally" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousFinally" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousWith a Source #

Constructors

AnonymousWith 

Fields

Instances
Eq a => Eq (AnonymousWith a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousWith a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousWith a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousWith a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousWith a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousWith a) Source # 
Instance details

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 (AnonymousWith a)

SymbolMatching (AnonymousWith a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousWith a) -> Node -> Bool

showFailure :: Proxy (AnonymousWith a) -> Node -> String

type Rep (AnonymousWith a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousWith a) = D1 (MetaData "AnonymousWith" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousWith" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousDef a Source #

Constructors

AnonymousDef 

Fields

Instances
Eq a => Eq (AnonymousDef a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousDef a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousDef a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousDef a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousDef a) :: Type -> Type #

Methods

from :: AnonymousDef a -> Rep (AnonymousDef a) x #

to :: Rep (AnonymousDef a) x -> AnonymousDef a #

Unmarshal a => Unmarshal (AnonymousDef a) Source # 
Instance details

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 (AnonymousDef a)

SymbolMatching (AnonymousDef a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousDef a) -> Node -> Bool

showFailure :: Proxy (AnonymousDef a) -> Node -> String

type Rep (AnonymousDef a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousDef a) = D1 (MetaData "AnonymousDef" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousDef" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousMinusRAngle a Source #

Constructors

AnonymousMinusRAngle 

Fields

Instances
Eq a => Eq (AnonymousMinusRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousMinusRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousMinusRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousMinusRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousMinusRAngle a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousMinusRAngle a) Source # 
Instance details

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 (AnonymousMinusRAngle a)

SymbolMatching (AnonymousMinusRAngle a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousMinusRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousMinusRAngle a) = D1 (MetaData "AnonymousMinusRAngle" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousMinusRAngle" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousEqual a Source #

Constructors

AnonymousEqual 

Fields

Instances
Eq a => Eq (AnonymousEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousEqual a) Source # 
Instance details

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 (AnonymousEqual a)

SymbolMatching (AnonymousEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousEqual a) -> Node -> Bool

showFailure :: Proxy (AnonymousEqual a) -> Node -> String

type Rep (AnonymousEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousEqual a) = D1 (MetaData "AnonymousEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousGlobal a Source #

Constructors

AnonymousGlobal 

Fields

Instances
Eq a => Eq (AnonymousGlobal a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousGlobal a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousGlobal a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousGlobal a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousGlobal a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousGlobal a) Source # 
Instance details

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 (AnonymousGlobal a)

SymbolMatching (AnonymousGlobal a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousGlobal a) -> Node -> Bool

showFailure :: Proxy (AnonymousGlobal a) -> Node -> String

type Rep (AnonymousGlobal a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousGlobal a) = D1 (MetaData "AnonymousGlobal" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousGlobal" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousNonlocal a Source #

Constructors

AnonymousNonlocal 

Fields

Instances
Eq a => Eq (AnonymousNonlocal a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousNonlocal a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousNonlocal a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousNonlocal a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousNonlocal a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousNonlocal a) Source # 
Instance details

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 (AnonymousNonlocal a)

SymbolMatching (AnonymousNonlocal a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousNonlocal a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousNonlocal a) = D1 (MetaData "AnonymousNonlocal" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousNonlocal" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousExec a Source #

Constructors

AnonymousExec 

Fields

Instances
Eq a => Eq (AnonymousExec a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousExec a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousExec a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousExec a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousExec a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousExec a) Source # 
Instance details

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 (AnonymousExec a)

SymbolMatching (AnonymousExec a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousExec a) -> Node -> Bool

showFailure :: Proxy (AnonymousExec a) -> Node -> String

type Rep (AnonymousExec a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousExec a) = D1 (MetaData "AnonymousExec" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousExec" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousClass a Source #

Constructors

AnonymousClass 

Fields

Instances
Eq a => Eq (AnonymousClass a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousClass a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousClass a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousClass a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousClass a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousClass a) Source # 
Instance details

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 (AnonymousClass a)

SymbolMatching (AnonymousClass a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousClass a) -> Node -> Bool

showFailure :: Proxy (AnonymousClass a) -> Node -> String

type Rep (AnonymousClass a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousClass a) = D1 (MetaData "AnonymousClass" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousClass" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousAt a Source #

Constructors

AnonymousAt 

Fields

Instances
Eq a => Eq (AnonymousAt a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousAt a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousAt a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousAt a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousAt a) :: Type -> Type #

Methods

from :: AnonymousAt a -> Rep (AnonymousAt a) x #

to :: Rep (AnonymousAt a) x -> AnonymousAt a #

Unmarshal a => Unmarshal (AnonymousAt a) Source # 
Instance details

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 (AnonymousAt a)

SymbolMatching (AnonymousAt a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousAt a) -> Node -> Bool

showFailure :: Proxy (AnonymousAt a) -> Node -> String

type Rep (AnonymousAt a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousAt a) = D1 (MetaData "AnonymousAt" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousAt" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousNot a Source #

Constructors

AnonymousNot 

Fields

Instances
Eq a => Eq (AnonymousNot a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousNot a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousNot a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousNot a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousNot a) :: Type -> Type #

Methods

from :: AnonymousNot a -> Rep (AnonymousNot a) x #

to :: Rep (AnonymousNot a) x -> AnonymousNot a #

Unmarshal a => Unmarshal (AnonymousNot a) Source # 
Instance details

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 (AnonymousNot a)

SymbolMatching (AnonymousNot a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousNot a) -> Node -> Bool

showFailure :: Proxy (AnonymousNot a) -> Node -> String

type Rep (AnonymousNot a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousNot a) = D1 (MetaData "AnonymousNot" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousNot" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousAnd a Source #

Constructors

AnonymousAnd 

Fields

Instances
Eq a => Eq (AnonymousAnd a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousAnd a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousAnd a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousAnd a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousAnd a) :: Type -> Type #

Methods

from :: AnonymousAnd a -> Rep (AnonymousAnd a) x #

to :: Rep (AnonymousAnd a) x -> AnonymousAnd a #

Unmarshal a => Unmarshal (AnonymousAnd a) Source # 
Instance details

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 (AnonymousAnd a)

SymbolMatching (AnonymousAnd a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousAnd a) -> Node -> Bool

showFailure :: Proxy (AnonymousAnd a) -> Node -> String

type Rep (AnonymousAnd a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousAnd a) = D1 (MetaData "AnonymousAnd" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousAnd" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousOr a Source #

Constructors

AnonymousOr 

Fields

Instances
Eq a => Eq (AnonymousOr a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousOr a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousOr a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousOr a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousOr a) :: Type -> Type #

Methods

from :: AnonymousOr a -> Rep (AnonymousOr a) x #

to :: Rep (AnonymousOr a) x -> AnonymousOr a #

Unmarshal a => Unmarshal (AnonymousOr a) Source # 
Instance details

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 (AnonymousOr a)

SymbolMatching (AnonymousOr a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousOr a) -> Node -> Bool

showFailure :: Proxy (AnonymousOr a) -> Node -> String

type Rep (AnonymousOr a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousOr a) = D1 (MetaData "AnonymousOr" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousOr" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousPlus a Source #

Constructors

AnonymousPlus 

Fields

Instances
Eq a => Eq (AnonymousPlus a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousPlus a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousPlus a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousPlus a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousPlus a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousPlus a) Source # 
Instance details

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 (AnonymousPlus a)

SymbolMatching (AnonymousPlus a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousPlus a) -> Node -> Bool

showFailure :: Proxy (AnonymousPlus a) -> Node -> String

type Rep (AnonymousPlus a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousPlus a) = D1 (MetaData "AnonymousPlus" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousPlus" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousMinus a Source #

Constructors

AnonymousMinus 

Fields

Instances
Eq a => Eq (AnonymousMinus a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousMinus a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousMinus a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousMinus a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousMinus a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousMinus a) Source # 
Instance details

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 (AnonymousMinus a)

SymbolMatching (AnonymousMinus a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousMinus a) -> Node -> Bool

showFailure :: Proxy (AnonymousMinus a) -> Node -> String

type Rep (AnonymousMinus a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousMinus a) = D1 (MetaData "AnonymousMinus" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousMinus" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousSlash a Source #

Constructors

AnonymousSlash 

Fields

Instances
Eq a => Eq (AnonymousSlash a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousSlash a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousSlash a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousSlash a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousSlash a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousSlash a) Source # 
Instance details

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 (AnonymousSlash a)

SymbolMatching (AnonymousSlash a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousSlash a) -> Node -> Bool

showFailure :: Proxy (AnonymousSlash a) -> Node -> String

type Rep (AnonymousSlash a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousSlash a) = D1 (MetaData "AnonymousSlash" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousSlash" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousPercent a Source #

Constructors

AnonymousPercent 

Fields

Instances
Eq a => Eq (AnonymousPercent a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousPercent a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousPercent a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousPercent a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousPercent a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousPercent a) Source # 
Instance details

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 (AnonymousPercent a)

SymbolMatching (AnonymousPercent a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousPercent a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousPercent a) = D1 (MetaData "AnonymousPercent" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousPercent" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousSlashSlash a Source #

Constructors

AnonymousSlashSlash 

Fields

Instances
Eq a => Eq (AnonymousSlashSlash a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousSlashSlash a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousSlashSlash a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousSlashSlash a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousSlashSlash a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousSlashSlash a) Source # 
Instance details

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 (AnonymousSlashSlash a)

SymbolMatching (AnonymousSlashSlash a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousSlashSlash a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousSlashSlash a) = D1 (MetaData "AnonymousSlashSlash" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousSlashSlash" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousStarStar a Source #

Constructors

AnonymousStarStar 

Fields

Instances
Eq a => Eq (AnonymousStarStar a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousStarStar a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousStarStar a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousStarStar a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousStarStar a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousStarStar a) Source # 
Instance details

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 (AnonymousStarStar a)

SymbolMatching (AnonymousStarStar a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousStarStar a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousStarStar a) = D1 (MetaData "AnonymousStarStar" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousStarStar" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousPipe a Source #

Constructors

AnonymousPipe 

Fields

Instances
Eq a => Eq (AnonymousPipe a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousPipe a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousPipe a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousPipe a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousPipe a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousPipe a) Source # 
Instance details

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 (AnonymousPipe a)

SymbolMatching (AnonymousPipe a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousPipe a) -> Node -> Bool

showFailure :: Proxy (AnonymousPipe a) -> Node -> String

type Rep (AnonymousPipe a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousPipe a) = D1 (MetaData "AnonymousPipe" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousPipe" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousAmpersand a Source #

Constructors

AnonymousAmpersand 

Fields

Instances
Eq a => Eq (AnonymousAmpersand a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousAmpersand a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousAmpersand a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousAmpersand a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousAmpersand a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousAmpersand a) Source # 
Instance details

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 (AnonymousAmpersand a)

SymbolMatching (AnonymousAmpersand a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousAmpersand a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousAmpersand a) = D1 (MetaData "AnonymousAmpersand" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousAmpersand" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousCaret a Source #

Constructors

AnonymousCaret 

Fields

Instances
Eq a => Eq (AnonymousCaret a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousCaret a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousCaret a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousCaret a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousCaret a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousCaret a) Source # 
Instance details

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 (AnonymousCaret a)

SymbolMatching (AnonymousCaret a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousCaret a) -> Node -> Bool

showFailure :: Proxy (AnonymousCaret a) -> Node -> String

type Rep (AnonymousCaret a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousCaret a) = D1 (MetaData "AnonymousCaret" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousCaret" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousLAngleLAngle a Source #

Constructors

AnonymousLAngleLAngle 

Fields

Instances
Eq a => Eq (AnonymousLAngleLAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousLAngleLAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousLAngleLAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousLAngleLAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousLAngleLAngle a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousLAngleLAngle a) Source # 
Instance details

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 (AnonymousLAngleLAngle a)

SymbolMatching (AnonymousLAngleLAngle a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLAngleLAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLAngleLAngle a) = D1 (MetaData "AnonymousLAngleLAngle" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousLAngleLAngle" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousTilde a Source #

Constructors

AnonymousTilde 

Fields

Instances
Eq a => Eq (AnonymousTilde a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousTilde a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousTilde a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousTilde a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousTilde a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousTilde a) Source # 
Instance details

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 (AnonymousTilde a)

SymbolMatching (AnonymousTilde a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousTilde a) -> Node -> Bool

showFailure :: Proxy (AnonymousTilde a) -> Node -> String

type Rep (AnonymousTilde a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousTilde a) = D1 (MetaData "AnonymousTilde" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousTilde" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousLAngle a Source #

Constructors

AnonymousLAngle 

Fields

Instances
Eq a => Eq (AnonymousLAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousLAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousLAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousLAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousLAngle a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousLAngle a) Source # 
Instance details

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 (AnonymousLAngle a)

SymbolMatching (AnonymousLAngle a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousLAngle a) -> Node -> Bool

showFailure :: Proxy (AnonymousLAngle a) -> Node -> String

type Rep (AnonymousLAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLAngle a) = D1 (MetaData "AnonymousLAngle" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousLAngle" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousLAngleEqual a Source #

Constructors

AnonymousLAngleEqual 

Fields

Instances
Eq a => Eq (AnonymousLAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousLAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousLAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousLAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousLAngleEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousLAngleEqual a) Source # 
Instance details

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 (AnonymousLAngleEqual a)

SymbolMatching (AnonymousLAngleEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLAngleEqual a) = D1 (MetaData "AnonymousLAngleEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousLAngleEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousEqualEqual a Source #

Constructors

AnonymousEqualEqual 

Fields

Instances
Eq a => Eq (AnonymousEqualEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousEqualEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousEqualEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousEqualEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousEqualEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousEqualEqual a) Source # 
Instance details

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 (AnonymousEqualEqual a)

SymbolMatching (AnonymousEqualEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousEqualEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousEqualEqual a) = D1 (MetaData "AnonymousEqualEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousEqualEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousBangEqual a Source #

Constructors

AnonymousBangEqual 

Fields

Instances
Eq a => Eq (AnonymousBangEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousBangEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousBangEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousBangEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousBangEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousBangEqual a) Source # 
Instance details

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 (AnonymousBangEqual a)

SymbolMatching (AnonymousBangEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousBangEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousBangEqual a) = D1 (MetaData "AnonymousBangEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousBangEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousRAngleEqual a Source #

Constructors

AnonymousRAngleEqual 

Fields

Instances
Eq a => Eq (AnonymousRAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousRAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousRAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousRAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousRAngleEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousRAngleEqual a) Source # 
Instance details

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 (AnonymousRAngleEqual a)

SymbolMatching (AnonymousRAngleEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousRAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousRAngleEqual a) = D1 (MetaData "AnonymousRAngleEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousRAngleEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousRAngle a Source #

Constructors

AnonymousRAngle 

Fields

Instances
Eq a => Eq (AnonymousRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousRAngle a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousRAngle a) Source # 
Instance details

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 (AnonymousRAngle a)

SymbolMatching (AnonymousRAngle a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousRAngle a) -> Node -> Bool

showFailure :: Proxy (AnonymousRAngle a) -> Node -> String

type Rep (AnonymousRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousRAngle a) = D1 (MetaData "AnonymousRAngle" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousRAngle" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousLAngleRAngle a Source #

Constructors

AnonymousLAngleRAngle 

Fields

Instances
Eq a => Eq (AnonymousLAngleRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousLAngleRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousLAngleRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousLAngleRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousLAngleRAngle a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousLAngleRAngle a) Source # 
Instance details

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 (AnonymousLAngleRAngle a)

SymbolMatching (AnonymousLAngleRAngle a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLAngleRAngle a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLAngleRAngle a) = D1 (MetaData "AnonymousLAngleRAngle" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousLAngleRAngle" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousIs a Source #

Constructors

AnonymousIs 

Fields

Instances
Eq a => Eq (AnonymousIs a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousIs a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousIs a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousIs a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousIs a) :: Type -> Type #

Methods

from :: AnonymousIs a -> Rep (AnonymousIs a) x #

to :: Rep (AnonymousIs a) x -> AnonymousIs a #

Unmarshal a => Unmarshal (AnonymousIs a) Source # 
Instance details

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 (AnonymousIs a)

SymbolMatching (AnonymousIs a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousIs a) -> Node -> Bool

showFailure :: Proxy (AnonymousIs a) -> Node -> String

type Rep (AnonymousIs a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousIs a) = D1 (MetaData "AnonymousIs" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousIs" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousLambda a Source #

Constructors

AnonymousLambda 

Fields

Instances
Eq a => Eq (AnonymousLambda a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousLambda a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousLambda a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousLambda a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousLambda a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousLambda a) Source # 
Instance details

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 (AnonymousLambda a)

SymbolMatching (AnonymousLambda a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousLambda a) -> Node -> Bool

showFailure :: Proxy (AnonymousLambda a) -> Node -> String

type Rep (AnonymousLambda a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLambda a) = D1 (MetaData "AnonymousLambda" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousLambda" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousPlusEqual a Source #

Constructors

AnonymousPlusEqual 

Fields

Instances
Eq a => Eq (AnonymousPlusEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousPlusEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousPlusEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousPlusEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousPlusEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousPlusEqual a) Source # 
Instance details

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 (AnonymousPlusEqual a)

SymbolMatching (AnonymousPlusEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousPlusEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousPlusEqual a) = D1 (MetaData "AnonymousPlusEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousPlusEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousMinusEqual a Source #

Constructors

AnonymousMinusEqual 

Fields

Instances
Eq a => Eq (AnonymousMinusEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousMinusEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousMinusEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousMinusEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousMinusEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousMinusEqual a) Source # 
Instance details

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 (AnonymousMinusEqual a)

SymbolMatching (AnonymousMinusEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousMinusEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousMinusEqual a) = D1 (MetaData "AnonymousMinusEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousMinusEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousStarEqual a Source #

Constructors

AnonymousStarEqual 

Fields

Instances
Eq a => Eq (AnonymousStarEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousStarEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousStarEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousStarEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousStarEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousStarEqual a) Source # 
Instance details

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 (AnonymousStarEqual a)

SymbolMatching (AnonymousStarEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousStarEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousStarEqual a) = D1 (MetaData "AnonymousStarEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousStarEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousSlashEqual a Source #

Constructors

AnonymousSlashEqual 

Fields

Instances
Eq a => Eq (AnonymousSlashEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousSlashEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousSlashEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousSlashEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousSlashEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousSlashEqual a) Source # 
Instance details

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 (AnonymousSlashEqual a)

SymbolMatching (AnonymousSlashEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousSlashEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousSlashEqual a) = D1 (MetaData "AnonymousSlashEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousSlashEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousAtEqual a Source #

Constructors

AnonymousAtEqual 

Fields

Instances
Eq a => Eq (AnonymousAtEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousAtEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousAtEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousAtEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousAtEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousAtEqual a) Source # 
Instance details

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 (AnonymousAtEqual a)

SymbolMatching (AnonymousAtEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousAtEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousAtEqual a) = D1 (MetaData "AnonymousAtEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousAtEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousSlashSlashEqual a Source #

Constructors

AnonymousSlashSlashEqual 

Fields

Instances
Eq a => Eq (AnonymousSlashSlashEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousSlashSlashEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousSlashSlashEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousSlashSlashEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousSlashSlashEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousSlashSlashEqual a) Source # 
Instance details

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 (AnonymousSlashSlashEqual a)

SymbolMatching (AnonymousSlashSlashEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousSlashSlashEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousSlashSlashEqual a) = D1 (MetaData "AnonymousSlashSlashEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousSlashSlashEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousPercentEqual a Source #

Constructors

AnonymousPercentEqual 

Fields

Instances
Eq a => Eq (AnonymousPercentEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousPercentEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousPercentEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousPercentEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousPercentEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousPercentEqual a) Source # 
Instance details

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 (AnonymousPercentEqual a)

SymbolMatching (AnonymousPercentEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousPercentEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousPercentEqual a) = D1 (MetaData "AnonymousPercentEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousPercentEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousStarStarEqual a Source #

Constructors

AnonymousStarStarEqual 

Fields

Instances
Eq a => Eq (AnonymousStarStarEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousStarStarEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousStarStarEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousStarStarEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousStarStarEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousStarStarEqual a) Source # 
Instance details

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 (AnonymousStarStarEqual a)

SymbolMatching (AnonymousStarStarEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousStarStarEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousStarStarEqual a) = D1 (MetaData "AnonymousStarStarEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousStarStarEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousRAngleRAngleEqual a Source #

Constructors

AnonymousRAngleRAngleEqual 

Fields

Instances
Eq a => Eq (AnonymousRAngleRAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousRAngleRAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousRAngleRAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousRAngleRAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousRAngleRAngleEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousRAngleRAngleEqual a) Source # 
Instance details

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 (AnonymousRAngleRAngleEqual a)

SymbolMatching (AnonymousRAngleRAngleEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousRAngleRAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousRAngleRAngleEqual a) = D1 (MetaData "AnonymousRAngleRAngleEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousRAngleRAngleEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousLAngleLAngleEqual a Source #

Constructors

AnonymousLAngleLAngleEqual 

Fields

Instances
Eq a => Eq (AnonymousLAngleLAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousLAngleLAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousLAngleLAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousLAngleLAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousLAngleLAngleEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousLAngleLAngleEqual a) Source # 
Instance details

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 (AnonymousLAngleLAngleEqual a)

SymbolMatching (AnonymousLAngleLAngleEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLAngleLAngleEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLAngleLAngleEqual a) = D1 (MetaData "AnonymousLAngleLAngleEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousLAngleLAngleEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousAmpersandEqual a Source #

Constructors

AnonymousAmpersandEqual 

Fields

Instances
Eq a => Eq (AnonymousAmpersandEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousAmpersandEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousAmpersandEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousAmpersandEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousAmpersandEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousAmpersandEqual a) Source # 
Instance details

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 (AnonymousAmpersandEqual a)

SymbolMatching (AnonymousAmpersandEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousAmpersandEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousAmpersandEqual a) = D1 (MetaData "AnonymousAmpersandEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousAmpersandEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousCaretEqual a Source #

Constructors

AnonymousCaretEqual 

Fields

Instances
Eq a => Eq (AnonymousCaretEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousCaretEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousCaretEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousCaretEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousCaretEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousCaretEqual a) Source # 
Instance details

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 (AnonymousCaretEqual a)

SymbolMatching (AnonymousCaretEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousCaretEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousCaretEqual a) = D1 (MetaData "AnonymousCaretEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousCaretEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousPipeEqual a Source #

Constructors

AnonymousPipeEqual 

Fields

Instances
Eq a => Eq (AnonymousPipeEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousPipeEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousPipeEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousPipeEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousPipeEqual a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousPipeEqual a) Source # 
Instance details

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 (AnonymousPipeEqual a)

SymbolMatching (AnonymousPipeEqual a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousPipeEqual a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousPipeEqual a) = D1 (MetaData "AnonymousPipeEqual" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousPipeEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousYield a Source #

Constructors

AnonymousYield 

Fields

Instances
Eq a => Eq (AnonymousYield a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousYield a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousYield a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousYield a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousYield a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousYield a) Source # 
Instance details

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 (AnonymousYield a)

SymbolMatching (AnonymousYield a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousYield a) -> Node -> Bool

showFailure :: Proxy (AnonymousYield a) -> Node -> String

type Rep (AnonymousYield a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousYield a) = D1 (MetaData "AnonymousYield" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousYield" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousLBracket a Source #

Constructors

AnonymousLBracket 

Fields

Instances
Eq a => Eq (AnonymousLBracket a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousLBracket a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousLBracket a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousLBracket a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousLBracket a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousLBracket a) Source # 
Instance details

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 (AnonymousLBracket a)

SymbolMatching (AnonymousLBracket a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLBracket a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLBracket a) = D1 (MetaData "AnonymousLBracket" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousLBracket" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousRBracket a Source #

Constructors

AnonymousRBracket 

Fields

Instances
Eq a => Eq (AnonymousRBracket a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousRBracket a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousRBracket a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousRBracket a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousRBracket a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousRBracket a) Source # 
Instance details

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 (AnonymousRBracket a)

SymbolMatching (AnonymousRBracket a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousRBracket a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousRBracket a) = D1 (MetaData "AnonymousRBracket" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousRBracket" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data Ellipsis a Source #

Constructors

Ellipsis 

Fields

Instances
Eq a => Eq (Ellipsis a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Ellipsis a -> Ellipsis a -> Bool #

(/=) :: Ellipsis a -> Ellipsis a -> Bool #

Ord a => Ord (Ellipsis a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Ellipsis a -> Ellipsis a -> Ordering #

(<) :: Ellipsis a -> Ellipsis a -> Bool #

(<=) :: Ellipsis a -> Ellipsis a -> Bool #

(>) :: Ellipsis a -> Ellipsis a -> Bool #

(>=) :: Ellipsis a -> Ellipsis a -> Bool #

max :: Ellipsis a -> Ellipsis a -> Ellipsis a #

min :: Ellipsis a -> Ellipsis a -> Ellipsis a #

Show a => Show (Ellipsis a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Ellipsis a -> ShowS #

show :: Ellipsis a -> String #

showList :: [Ellipsis a] -> ShowS #

Generic (Ellipsis a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Ellipsis a) :: Type -> Type #

Methods

from :: Ellipsis a -> Rep (Ellipsis a) x #

to :: Rep (Ellipsis a) x -> Ellipsis a #

Unmarshal a => Unmarshal (Ellipsis a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Ellipsis a) -> Node -> Bool

showFailure :: Proxy (Ellipsis a) -> Node -> String

type Rep (Ellipsis a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Ellipsis a) = D1 (MetaData "Ellipsis" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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
Eq a => Eq (AnonymousLBrace a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousLBrace a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousLBrace a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousLBrace a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousLBrace a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousLBrace a) Source # 
Instance details

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 (AnonymousLBrace a)

SymbolMatching (AnonymousLBrace a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousLBrace a) -> Node -> Bool

showFailure :: Proxy (AnonymousLBrace a) -> Node -> String

type Rep (AnonymousLBrace a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousLBrace a) = D1 (MetaData "AnonymousLBrace" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousLBrace" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype AnonymousRBrace a Source #

Constructors

AnonymousRBrace 

Fields

Instances
Eq a => Eq (AnonymousRBrace a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousRBrace a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousRBrace a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousRBrace a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousRBrace a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousRBrace a) Source # 
Instance details

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 (AnonymousRBrace a)

SymbolMatching (AnonymousRBrace a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousRBrace a) -> Node -> Bool

showFailure :: Proxy (AnonymousRBrace a) -> Node -> String

type Rep (AnonymousRBrace a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousRBrace a) = D1 (MetaData "AnonymousRBrace" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousRBrace" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data EscapeSequence a Source #

Constructors

EscapeSequence 

Fields

Instances
Eq a => Eq (EscapeSequence a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (EscapeSequence a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (EscapeSequence a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (EscapeSequence a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (EscapeSequence a) :: Type -> Type #

Unmarshal a => Unmarshal (EscapeSequence a) Source # 
Instance details

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 (EscapeSequence a)

SymbolMatching (EscapeSequence a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (EscapeSequence a) -> Node -> Bool

showFailure :: Proxy (EscapeSequence a) -> Node -> String

type Rep (EscapeSequence a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (EscapeSequence a) = D1 (MetaData "EscapeSequence" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "EscapeSequence" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data TypeConversion a Source #

Constructors

TypeConversion 

Fields

Instances
Eq a => Eq (TypeConversion a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (TypeConversion a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (TypeConversion a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (TypeConversion a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (TypeConversion a) :: Type -> Type #

Unmarshal a => Unmarshal (TypeConversion a) Source # 
Instance details

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 (TypeConversion a)

SymbolMatching (TypeConversion a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (TypeConversion a) -> Node -> Bool

showFailure :: Proxy (TypeConversion a) -> Node -> String

type Rep (TypeConversion a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (TypeConversion a) = D1 (MetaData "TypeConversion" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "TypeConversion" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Integer a Source #

Constructors

Integer 

Fields

Instances
Eq a => Eq (Integer a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Integer a -> Integer a -> Bool #

(/=) :: Integer a -> Integer a -> Bool #

Ord a => Ord (Integer a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Integer a -> Integer a -> Ordering #

(<) :: Integer a -> Integer a -> Bool #

(<=) :: Integer a -> Integer a -> Bool #

(>) :: Integer a -> Integer a -> Bool #

(>=) :: Integer a -> Integer a -> Bool #

max :: Integer a -> Integer a -> Integer a #

min :: Integer a -> Integer a -> Integer a #

Show a => Show (Integer a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Integer a -> ShowS #

show :: Integer a -> String #

showList :: [Integer a] -> ShowS #

Generic (Integer a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Integer a) :: Type -> Type #

Methods

from :: Integer a -> Rep (Integer a) x #

to :: Rep (Integer a) x -> Integer a #

Unmarshal a => Unmarshal (Integer a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Integer a) -> Node -> Bool

showFailure :: Proxy (Integer a) -> Node -> String

type Rep (Integer a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Integer a) = D1 (MetaData "Integer" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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)))

data Float a Source #

Constructors

Float 

Fields

Instances
Eq a => Eq (Float a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Float a -> Float a -> Bool #

(/=) :: Float a -> Float a -> Bool #

Ord a => Ord (Float a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Float a -> Float a -> Ordering #

(<) :: Float a -> Float a -> Bool #

(<=) :: Float a -> Float a -> Bool #

(>) :: Float a -> Float a -> Bool #

(>=) :: Float a -> Float a -> Bool #

max :: Float a -> Float a -> Float a #

min :: Float a -> Float a -> Float a #

Show a => Show (Float a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Float a -> ShowS #

show :: Float a -> String #

showList :: [Float a] -> ShowS #

Generic (Float a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Float a) :: Type -> Type #

Methods

from :: Float a -> Rep (Float a) x #

to :: Rep (Float a) x -> Float a #

Unmarshal a => Unmarshal (Float a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Float a) -> Node -> Bool

showFailure :: Proxy (Float a) -> Node -> String

type Rep (Float a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Float a) = D1 (MetaData "Float" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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 

Fields

Instances
Eq a => Eq (Identifier a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Identifier a -> Identifier a -> Bool #

(/=) :: Identifier a -> Identifier a -> Bool #

Ord a => Ord (Identifier a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (Identifier a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (Identifier a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Identifier a) :: Type -> Type #

Methods

from :: Identifier a -> Rep (Identifier a) x #

to :: Rep (Identifier a) x -> Identifier a #

Unmarshal a => Unmarshal (Identifier a) Source # 
Instance details

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 (Identifier a)

SymbolMatching (Identifier a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Identifier a) -> Node -> Bool

showFailure :: Proxy (Identifier a) -> Node -> String

type Rep (Identifier a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Identifier a) = D1 (MetaData "Identifier" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "Identifier" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "bytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data NonlocalStatement a Source #

Constructors

NonlocalStatement 

Fields

Instances
Eq a => Eq (NonlocalStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (NonlocalStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (NonlocalStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (NonlocalStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (NonlocalStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (NonlocalStatement a) Source # 
Instance details

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 (NonlocalStatement a)

SymbolMatching (NonlocalStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (NonlocalStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (NonlocalStatement a) = D1 (MetaData "NonlocalStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "NonlocalStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Identifier a)))))

data GlobalStatement a Source #

Constructors

GlobalStatement 

Fields

Instances
Eq a => Eq (GlobalStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (GlobalStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (GlobalStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (GlobalStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (GlobalStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (GlobalStatement a) Source # 
Instance details

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 (GlobalStatement a)

SymbolMatching (GlobalStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (GlobalStatement a) -> Node -> Bool

showFailure :: Proxy (GlobalStatement a) -> Node -> String

type Rep (GlobalStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (GlobalStatement a) = D1 (MetaData "GlobalStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "GlobalStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Identifier a)))))

data DottedName a Source #

Constructors

DottedName 

Fields

Instances
Eq a => Eq (DottedName a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: DottedName a -> DottedName a -> Bool #

(/=) :: DottedName a -> DottedName a -> Bool #

Ord a => Ord (DottedName a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (DottedName a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (DottedName a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (DottedName a) :: Type -> Type #

Methods

from :: DottedName a -> Rep (DottedName a) x #

to :: Rep (DottedName a) x -> DottedName a #

Unmarshal a => Unmarshal (DottedName a) Source # 
Instance details

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 (DottedName a)

SymbolMatching (DottedName a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (DottedName a) -> Node -> Bool

showFailure :: Proxy (DottedName a) -> Node -> String

type Rep (DottedName a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (DottedName a) = D1 (MetaData "DottedName" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "DottedName" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Identifier a)))))

data RelativeImport a Source #

Constructors

RelativeImport 
Instances
Eq a => Eq (RelativeImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (RelativeImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (RelativeImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (RelativeImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (RelativeImport a) :: Type -> Type #

Unmarshal a => Unmarshal (RelativeImport a) Source # 
Instance details

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 (RelativeImport a)

SymbolMatching (RelativeImport a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (RelativeImport a) -> Node -> Bool

showFailure :: Proxy (RelativeImport a) -> Node -> String

type Rep (RelativeImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (RelativeImport a) = D1 (MetaData "RelativeImport" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "RelativeImport" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Either (DottedName a) (ImportPrefix a))))))

data AliasedImport a Source #

Constructors

AliasedImport 

Fields

Instances
Eq a => Eq (AliasedImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AliasedImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AliasedImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AliasedImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AliasedImport a) :: Type -> Type #

Unmarshal a => Unmarshal (AliasedImport a) Source # 
Instance details

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 (AliasedImport a)

SymbolMatching (AliasedImport a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AliasedImport a) -> Node -> Bool

showFailure :: Proxy (AliasedImport a) -> Node -> String

type Rep (AliasedImport a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AliasedImport a) = D1 (MetaData "AliasedImport" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "AliasedImport" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "alias") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Identifier a)) :*: S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DottedName a)))))

data ImportStatement a Source #

Constructors

ImportStatement 

Fields

Instances
Eq a => Eq (ImportStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ImportStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ImportStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ImportStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ImportStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (ImportStatement a) Source # 
Instance details

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 (ImportStatement a)

SymbolMatching (ImportStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (ImportStatement a) -> Node -> Bool

showFailure :: Proxy (ImportStatement a) -> Node -> String

type Rep (ImportStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ImportStatement a) = D1 (MetaData "ImportStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ImportStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either (AliasedImport a) (DottedName a)])))

data ImportFromStatement a Source #

Instances
Eq a => Eq (ImportFromStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ImportFromStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ImportFromStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ImportFromStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ImportFromStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (ImportFromStatement a) Source # 
Instance details

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 (ImportFromStatement a)

SymbolMatching (ImportFromStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ImportFromStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

data FutureImportStatement a Source #

Constructors

FutureImportStatement 

Fields

Instances
Eq a => Eq (FutureImportStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (FutureImportStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (FutureImportStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (FutureImportStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (FutureImportStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (FutureImportStatement a) Source # 
Instance details

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 (FutureImportStatement a)

SymbolMatching (FutureImportStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (FutureImportStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (FutureImportStatement a) = D1 (MetaData "FutureImportStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "FutureImportStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either (AliasedImport a) (DottedName a)])))

data True a Source #

Constructors

True 

Fields

Instances
Eq a => Eq (True a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: True a -> True a -> Bool #

(/=) :: True a -> True a -> Bool #

Ord a => Ord (True a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: True a -> True a -> Ordering #

(<) :: True a -> True a -> Bool #

(<=) :: True a -> True a -> Bool #

(>) :: True a -> True a -> Bool #

(>=) :: True a -> True a -> Bool #

max :: True a -> True a -> True a #

min :: True a -> True a -> True a #

Show a => Show (True a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> True a -> ShowS #

show :: True a -> String #

showList :: [True a] -> ShowS #

Generic (True a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (True a) :: Type -> Type #

Methods

from :: True a -> Rep (True a) x #

to :: Rep (True a) x -> True a #

Unmarshal a => Unmarshal (True a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (True a) -> Node -> Bool

showFailure :: Proxy (True a) -> Node -> String

type Rep (True a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (True a) = D1 (MetaData "True" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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)))

data False a Source #

Constructors

False 

Fields

Instances
Eq a => Eq (False a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: False a -> False a -> Bool #

(/=) :: False a -> False a -> Bool #

Ord a => Ord (False a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: False a -> False a -> Ordering #

(<) :: False a -> False a -> Bool #

(<=) :: False a -> False a -> Bool #

(>) :: False a -> False a -> Bool #

(>=) :: False a -> False a -> Bool #

max :: False a -> False a -> False a #

min :: False a -> False a -> False a #

Show a => Show (False a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> False a -> ShowS #

show :: False a -> String #

showList :: [False a] -> ShowS #

Generic (False a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (False a) :: Type -> Type #

Methods

from :: False a -> Rep (False a) x #

to :: Rep (False a) x -> False a #

Unmarshal a => Unmarshal (False a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (False a) -> Node -> Bool

showFailure :: Proxy (False a) -> Node -> String

type Rep (False a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (False a) = D1 (MetaData "False" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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)))

data None a Source #

Constructors

None 

Fields

Instances
Eq a => Eq (None a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: None a -> None a -> Bool #

(/=) :: None a -> None a -> Bool #

Ord a => Ord (None a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: None a -> None a -> Ordering #

(<) :: None a -> None a -> Bool #

(<=) :: None a -> None a -> Bool #

(>) :: None a -> None a -> Bool #

(>=) :: None a -> None a -> Bool #

max :: None a -> None a -> None a #

min :: None a -> None a -> None a #

Show a => Show (None a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> None a -> ShowS #

show :: None a -> String #

showList :: [None a] -> ShowS #

Generic (None a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (None a) :: Type -> Type #

Methods

from :: None a -> Rep (None a) x #

to :: Rep (None a) x -> None a #

Unmarshal a => Unmarshal (None a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (None a) -> Node -> Bool

showFailure :: Proxy (None a) -> Node -> String

type Rep (None a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (None a) = D1 (MetaData "None" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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 #

Instances
Eq a => Eq (PrimaryExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (PrimaryExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (PrimaryExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (PrimaryExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (PrimaryExpression a) :: Type -> Type #

Unmarshal a => Unmarshal (PrimaryExpression a) Source # 
Instance details

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 (PrimaryExpression a)

SymbolMatching (PrimaryExpression a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (PrimaryExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (PrimaryExpression a) = D1 (MetaData "PrimaryExpression" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) ((((C1 (MetaCons "AttributePrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Attribute a))) :+: C1 (MetaCons "BinaryOperatorPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (BinaryOperator a)))) :+: (C1 (MetaCons "CallPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Call a))) :+: (C1 (MetaCons "ConcatenatedStringPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ConcatenatedString a))) :+: C1 (MetaCons "DictionaryPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Dictionary a)))))) :+: ((C1 (MetaCons "DictionaryComprehensionPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DictionaryComprehension a))) :+: (C1 (MetaCons "EllipsisPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ellipsis a))) :+: C1 (MetaCons "FalsePrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (False a))))) :+: (C1 (MetaCons "FloatPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float a))) :+: (C1 (MetaCons "GeneratorExpressionPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (GeneratorExpression a))) :+: C1 (MetaCons "IdentifierPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Identifier a))))))) :+: (((C1 (MetaCons "IntegerPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Integer a))) :+: (C1 (MetaCons "ListPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (List a))) :+: C1 (MetaCons "ListComprehensionPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ListComprehension a))))) :+: (C1 (MetaCons "NonePrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (None a))) :+: (C1 (MetaCons "ParenthesizedExpressionPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ParenthesizedExpression a))) :+: C1 (MetaCons "SetPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set a)))))) :+: ((C1 (MetaCons "SetComprehensionPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SetComprehension a))) :+: (C1 (MetaCons "StringPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (String a))) :+: C1 (MetaCons "SubscriptPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Subscript a))))) :+: (C1 (MetaCons "TruePrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (True a))) :+: (C1 (MetaCons "TuplePrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Tuple a))) :+: C1 (MetaCons "UnaryOperatorPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (UnaryOperator a))))))))

data UnaryOperator a Source #

Instances
Eq a => Eq (UnaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (UnaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (UnaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (UnaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (UnaryOperator a) :: Type -> Type #

Unmarshal a => Unmarshal (UnaryOperator a) Source # 
Instance details

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 (UnaryOperator a)

SymbolMatching (UnaryOperator a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (UnaryOperator a) -> Node -> Bool

showFailure :: Proxy (UnaryOperator a) -> Node -> String

type Rep (UnaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (UnaryOperator a) = D1 (MetaData "UnaryOperator" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "UnaryOperator" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "operator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either (AnonymousPlus a) (Either (AnonymousMinus a) (AnonymousTilde a)))) :*: S1 (MetaSel (Just "argument") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PrimaryExpression a)))))

data Tuple a Source #

Constructors

Tuple 

Fields

Instances
Eq a => Eq (Tuple a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Tuple a -> Tuple a -> Bool #

(/=) :: Tuple a -> Tuple a -> Bool #

Ord a => Ord (Tuple a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Tuple a -> Tuple a -> Ordering #

(<) :: Tuple a -> Tuple a -> Bool #

(<=) :: Tuple a -> Tuple a -> Bool #

(>) :: Tuple a -> Tuple a -> Bool #

(>=) :: Tuple a -> Tuple a -> Bool #

max :: Tuple a -> Tuple a -> Tuple a #

min :: Tuple a -> Tuple a -> Tuple a #

Show a => Show (Tuple a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Tuple a -> ShowS #

show :: Tuple a -> String #

showList :: [Tuple a] -> ShowS #

Generic (Tuple a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Tuple a) :: Type -> Type #

Methods

from :: Tuple a -> Rep (Tuple a) x #

to :: Rep (Tuple a) x -> Tuple a #

Unmarshal a => Unmarshal (Tuple a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Tuple a) -> Node -> Bool

showFailure :: Proxy (Tuple a) -> Node -> String

type Rep (Tuple a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Tuple a) = D1 (MetaData "Tuple" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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)])))

data Yield a Source #

Constructors

Yield 

Fields

Instances
Eq a => Eq (Yield a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Yield a -> Yield a -> Bool #

(/=) :: Yield a -> Yield a -> Bool #

Ord a => Ord (Yield a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Yield a -> Yield a -> Ordering #

(<) :: Yield a -> Yield a -> Bool #

(<=) :: Yield a -> Yield a -> Bool #

(>) :: Yield a -> Yield a -> Bool #

(>=) :: Yield a -> Yield a -> Bool #

max :: Yield a -> Yield a -> Yield a #

min :: Yield a -> Yield a -> Yield a #

Show a => Show (Yield a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Yield a -> ShowS #

show :: Yield a -> String #

showList :: [Yield a] -> ShowS #

Generic (Yield a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Yield a) :: Type -> Type #

Methods

from :: Yield a -> Rep (Yield a) x #

to :: Rep (Yield a) x -> Yield a #

Unmarshal a => Unmarshal (Yield a) Source # 
Instance details

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 (Yield a)

SymbolMatching (Yield a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Yield a) -> Node -> Bool

showFailure :: Proxy (Yield a) -> Node -> String

type Rep (Yield a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Yield a) = D1 (MetaData "Yield" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "Yield" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Either (Expression a) (ExpressionList a))))))

data ExpressionList a Source #

Constructors

ExpressionList 

Fields

Instances
Eq a => Eq (ExpressionList a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ExpressionList a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ExpressionList a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ExpressionList a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ExpressionList a) :: Type -> Type #

Unmarshal a => Unmarshal (ExpressionList a) Source # 
Instance details

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 (ExpressionList a)

SymbolMatching (ExpressionList a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (ExpressionList a) -> Node -> Bool

showFailure :: Proxy (ExpressionList a) -> Node -> String

type Rep (ExpressionList a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ExpressionList a) = D1 (MetaData "ExpressionList" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ExpressionList" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Expression a)))))

data Expression a Source #

Instances
Eq a => Eq (Expression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Expression a -> Expression a -> Bool #

(/=) :: Expression a -> Expression a -> Bool #

Ord a => Ord (Expression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (Expression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (Expression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Expression a) :: Type -> Type #

Methods

from :: Expression a -> Rep (Expression a) x #

to :: Rep (Expression a) x -> Expression a #

Unmarshal a => Unmarshal (Expression a) Source # 
Instance details

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 (Expression a)

SymbolMatching (Expression a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Expression a) -> Node -> Bool

showFailure :: Proxy (Expression a) -> Node -> String

type Rep (Expression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Expression a) = D1 (MetaData "Expression" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (((C1 (MetaCons "PrimaryExpressionExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PrimaryExpression a))) :+: C1 (MetaCons "AwaitExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Await a)))) :+: (C1 (MetaCons "BooleanOperatorExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (BooleanOperator a))) :+: C1 (MetaCons "ComparisonOperatorExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ComparisonOperator a))))) :+: ((C1 (MetaCons "ConditionalExpressionExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ConditionalExpression a))) :+: C1 (MetaCons "LambdaExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Lambda a)))) :+: (C1 (MetaCons "NamedExpressionExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NamedExpression a))) :+: C1 (MetaCons "NotOperatorExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NotOperator a))))))

data NotOperator a Source #

Constructors

NotOperator 

Fields

Instances
Eq a => Eq (NotOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (NotOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (NotOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (NotOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (NotOperator a) :: Type -> Type #

Methods

from :: NotOperator a -> Rep (NotOperator a) x #

to :: Rep (NotOperator a) x -> NotOperator a #

Unmarshal a => Unmarshal (NotOperator a) Source # 
Instance details

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 (NotOperator a)

SymbolMatching (NotOperator a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (NotOperator a) -> Node -> Bool

showFailure :: Proxy (NotOperator a) -> Node -> String

type Rep (NotOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (NotOperator a) = D1 (MetaData "NotOperator" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "NotOperator" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "argument") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a))))

data NamedExpression a Source #

Constructors

NamedExpression 

Fields

Instances
Eq a => Eq (NamedExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (NamedExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (NamedExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (NamedExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (NamedExpression a) :: Type -> Type #

Unmarshal a => Unmarshal (NamedExpression a) Source # 
Instance details

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 (NamedExpression a)

SymbolMatching (NamedExpression a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (NamedExpression a) -> Node -> Bool

showFailure :: Proxy (NamedExpression a) -> Node -> String

type Rep (NamedExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (NamedExpression a) = D1 (MetaData "NamedExpression" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "NamedExpression" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "value") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a)) :*: S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Identifier a)))))

data Lambda a Source #

Constructors

Lambda 

Fields

Instances
Eq a => Eq (Lambda a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Lambda a -> Lambda a -> Bool #

(/=) :: Lambda a -> Lambda a -> Bool #

Ord a => Ord (Lambda a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Lambda a -> Lambda a -> Ordering #

(<) :: Lambda a -> Lambda a -> Bool #

(<=) :: Lambda a -> Lambda a -> Bool #

(>) :: Lambda a -> Lambda a -> Bool #

(>=) :: Lambda a -> Lambda a -> Bool #

max :: Lambda a -> Lambda a -> Lambda a #

min :: Lambda a -> Lambda a -> Lambda a #

Show a => Show (Lambda a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Lambda a -> ShowS #

show :: Lambda a -> String #

showList :: [Lambda a] -> ShowS #

Generic (Lambda a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Lambda a) :: Type -> Type #

Methods

from :: Lambda a -> Rep (Lambda a) x #

to :: Rep (Lambda a) x -> Lambda a #

Unmarshal a => Unmarshal (Lambda a) Source # 
Instance details

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 (Lambda a)

SymbolMatching (Lambda a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Lambda a) -> Node -> Bool

showFailure :: Proxy (Lambda a) -> Node -> String

type Rep (Lambda a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Lambda a) = D1 (MetaData "Lambda" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "Lambda" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either (Expression a) (Lambda a))) :*: S1 (MetaSel (Just "parameters") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (LambdaParameters a))))))

data LambdaParameters a Source #

Constructors

LambdaParameters 

Fields

Instances
Eq a => Eq (LambdaParameters a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (LambdaParameters a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (LambdaParameters a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (LambdaParameters a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (LambdaParameters a) :: Type -> Type #

Unmarshal a => Unmarshal (LambdaParameters a) Source # 
Instance details

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 (LambdaParameters a)

SymbolMatching (LambdaParameters a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (LambdaParameters a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (LambdaParameters a) = D1 (MetaData "LambdaParameters" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "LambdaParameters" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Parameter a)))))

data Parameter a Source #

Instances
Eq a => Eq (Parameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Parameter a -> Parameter a -> Bool #

(/=) :: Parameter a -> Parameter a -> Bool #

Ord a => Ord (Parameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (Parameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (Parameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Parameter a) :: Type -> Type #

Methods

from :: Parameter a -> Rep (Parameter a) x #

to :: Rep (Parameter a) x -> Parameter a #

Unmarshal a => Unmarshal (Parameter a) Source # 
Instance details

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 (Parameter a)

SymbolMatching (Parameter a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Parameter a) -> Node -> Bool

showFailure :: Proxy (Parameter a) -> Node -> String

type Rep (Parameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

data TypedParameter a Source #

Constructors

TypedParameter 

Fields

Instances
Eq a => Eq (TypedParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (TypedParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (TypedParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (TypedParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (TypedParameter a) :: Type -> Type #

Unmarshal a => Unmarshal (TypedParameter a) Source # 
Instance details

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 (TypedParameter a)

SymbolMatching (TypedParameter a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (TypedParameter a) -> Node -> Bool

showFailure :: Proxy (TypedParameter a) -> Node -> String

type Rep (TypedParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (TypedParameter a) = D1 (MetaData "TypedParameter" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "TypedParameter" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a)) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either (DictionarySplat a) (Either (Identifier a) (ListSplat a)))))))

data Type a Source #

Constructors

Type 

Fields

Instances
Eq a => Eq (Type a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Type a -> Type a -> Bool #

(/=) :: Type a -> Type a -> Bool #

Ord a => Ord (Type a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Type a -> Type a -> Ordering #

(<) :: Type a -> Type a -> Bool #

(<=) :: Type a -> Type a -> Bool #

(>) :: Type a -> Type a -> Bool #

(>=) :: Type a -> Type a -> Bool #

max :: Type a -> Type a -> Type a #

min :: Type a -> Type a -> Type a #

Show a => Show (Type a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Type a -> ShowS #

show :: Type a -> String #

showList :: [Type a] -> ShowS #

Generic (Type a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Type a) :: Type -> Type #

Methods

from :: Type a -> Rep (Type a) x #

to :: Rep (Type a) x -> Type a #

Unmarshal a => Unmarshal (Type a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Type a) -> Node -> Bool

showFailure :: Proxy (Type a) -> Node -> String

type Rep (Type a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Type a) = D1 (MetaData "Type" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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))))

data ListSplat a Source #

Constructors

ListSplat 

Fields

Instances
Eq a => Eq (ListSplat a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: ListSplat a -> ListSplat a -> Bool #

(/=) :: ListSplat a -> ListSplat a -> Bool #

Ord a => Ord (ListSplat a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ListSplat a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ListSplat a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ListSplat a) :: Type -> Type #

Methods

from :: ListSplat a -> Rep (ListSplat a) x #

to :: Rep (ListSplat a) x -> ListSplat a #

Unmarshal a => Unmarshal (ListSplat a) Source # 
Instance details

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 (ListSplat a)

SymbolMatching (ListSplat a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (ListSplat a) -> Node -> Bool

showFailure :: Proxy (ListSplat a) -> Node -> String

type Rep (ListSplat a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ListSplat a) = D1 (MetaData "ListSplat" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ListSplat" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Expression a)))))

data DictionarySplat a Source #

Constructors

DictionarySplat 

Fields

Instances
Eq a => Eq (DictionarySplat a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (DictionarySplat a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (DictionarySplat a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (DictionarySplat a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (DictionarySplat a) :: Type -> Type #

Unmarshal a => Unmarshal (DictionarySplat a) Source # 
Instance details

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 (DictionarySplat a)

SymbolMatching (DictionarySplat a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (DictionarySplat a) -> Node -> Bool

showFailure :: Proxy (DictionarySplat a) -> Node -> String

type Rep (DictionarySplat a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (DictionarySplat a) = D1 (MetaData "DictionarySplat" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "DictionarySplat" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a))))

data TypedDefaultParameter a Source #

Constructors

TypedDefaultParameter 

Fields

Instances
Eq a => Eq (TypedDefaultParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (TypedDefaultParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (TypedDefaultParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (TypedDefaultParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (TypedDefaultParameter a) :: Type -> Type #

Unmarshal a => Unmarshal (TypedDefaultParameter a) Source # 
Instance details

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 (TypedDefaultParameter a)

SymbolMatching (TypedDefaultParameter a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (TypedDefaultParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (TypedDefaultParameter a) = D1 (MetaData "TypedDefaultParameter" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "TypedDefaultParameter" PrefixI True) ((S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "value") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a))) :*: (S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Identifier a)) :*: S1 (MetaSel (Just "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a)))))

data DefaultParameter a Source #

Constructors

DefaultParameter 

Fields

Instances
Eq a => Eq (DefaultParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (DefaultParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (DefaultParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (DefaultParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (DefaultParameter a) :: Type -> Type #

Unmarshal a => Unmarshal (DefaultParameter a) Source # 
Instance details

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 (DefaultParameter a)

SymbolMatching (DefaultParameter a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (DefaultParameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (DefaultParameter a) = D1 (MetaData "DefaultParameter" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "DefaultParameter" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "value") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a)) :*: S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Identifier a)))))

data ConditionalExpression a Source #

Constructors

ConditionalExpression 

Fields

Instances
Eq a => Eq (ConditionalExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ConditionalExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ConditionalExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ConditionalExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ConditionalExpression a) :: Type -> Type #

Unmarshal a => Unmarshal (ConditionalExpression a) Source # 
Instance details

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 (ConditionalExpression a)

SymbolMatching (ConditionalExpression a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ConditionalExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ConditionalExpression a) = D1 (MetaData "ConditionalExpression" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ConditionalExpression" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Expression a)))))

data ComparisonOperator a Source #

Constructors

ComparisonOperator 
Instances
Eq a => Eq (ComparisonOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ComparisonOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ComparisonOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ComparisonOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ComparisonOperator a) :: Type -> Type #

Unmarshal a => Unmarshal (ComparisonOperator a) Source # 
Instance details

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 (ComparisonOperator a)

SymbolMatching (ComparisonOperator a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ComparisonOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ComparisonOperator a) = D1 (MetaData "ComparisonOperator" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ComparisonOperator" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (PrimaryExpression a)))))

data BooleanOperator a Source #

Constructors

BooleanOperator 

Fields

Instances
Eq a => Eq (BooleanOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (BooleanOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (BooleanOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (BooleanOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (BooleanOperator a) :: Type -> Type #

Unmarshal a => Unmarshal (BooleanOperator a) Source # 
Instance details

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 (BooleanOperator a)

SymbolMatching (BooleanOperator a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (BooleanOperator a) -> Node -> Bool

showFailure :: Proxy (BooleanOperator a) -> Node -> String

type Rep (BooleanOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

data Await a Source #

Constructors

Await 

Fields

Instances
Eq a => Eq (Await a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Await a -> Await a -> Bool #

(/=) :: Await a -> Await a -> Bool #

Ord a => Ord (Await a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Await a -> Await a -> Ordering #

(<) :: Await a -> Await a -> Bool #

(<=) :: Await a -> Await a -> Bool #

(>) :: Await a -> Await a -> Bool #

(>=) :: Await a -> Await a -> Bool #

max :: Await a -> Await a -> Await a #

min :: Await a -> Await a -> Await a #

Show a => Show (Await a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Await a -> ShowS #

show :: Await a -> String #

showList :: [Await a] -> ShowS #

Generic (Await a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Await a) :: Type -> Type #

Methods

from :: Await a -> Rep (Await a) x #

to :: Rep (Await a) x -> Await a #

Unmarshal a => Unmarshal (Await a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Await a) -> Node -> Bool

showFailure :: Proxy (Await a) -> Node -> String

type Rep (Await a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Await a) = D1 (MetaData "Await" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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))))

data Subscript a Source #

Constructors

Subscript 
Instances
Eq a => Eq (Subscript a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Subscript a -> Subscript a -> Bool #

(/=) :: Subscript a -> Subscript a -> Bool #

Ord a => Ord (Subscript a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (Subscript a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (Subscript a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Subscript a) :: Type -> Type #

Methods

from :: Subscript a -> Rep (Subscript a) x #

to :: Rep (Subscript a) x -> Subscript a #

Unmarshal a => Unmarshal (Subscript a) Source # 
Instance details

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 (Subscript a)

SymbolMatching (Subscript a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Subscript a) -> Node -> Bool

showFailure :: Proxy (Subscript a) -> Node -> String

type Rep (Subscript a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Subscript a) = D1 (MetaData "Subscript" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "Subscript" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "subscript") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Either (AnonymousComma a) (Either (Expression a) (Slice a))))) :*: S1 (MetaSel (Just "value") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PrimaryExpression a)))))

data Slice a Source #

Constructors

Slice 

Fields

Instances
Eq a => Eq (Slice a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Slice a -> Slice a -> Bool #

(/=) :: Slice a -> Slice a -> Bool #

Ord a => Ord (Slice a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Slice a -> Slice a -> Ordering #

(<) :: Slice a -> Slice a -> Bool #

(<=) :: Slice a -> Slice a -> Bool #

(>) :: Slice a -> Slice a -> Bool #

(>=) :: Slice a -> Slice a -> Bool #

max :: Slice a -> Slice a -> Slice a #

min :: Slice a -> Slice a -> Slice a #

Show a => Show (Slice a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Slice a -> ShowS #

show :: Slice a -> String #

showList :: [Slice a] -> ShowS #

Generic (Slice a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Slice a) :: Type -> Type #

Methods

from :: Slice a -> Rep (Slice a) x #

to :: Rep (Slice a) x -> Slice a #

Unmarshal a => Unmarshal (Slice a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Slice a) -> Node -> Bool

showFailure :: Proxy (Slice a) -> Node -> String

type Rep (Slice a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Slice a) = D1 (MetaData "Slice" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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])))

data String a Source #

Constructors

String 

Fields

Instances
Eq a => Eq (String a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: String a -> String a -> Bool #

(/=) :: String a -> String a -> Bool #

Ord a => Ord (String a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: String a -> String a -> Ordering #

(<) :: String a -> String a -> Bool #

(<=) :: String a -> String a -> Bool #

(>) :: String a -> String a -> Bool #

(>=) :: String a -> String a -> Bool #

max :: String a -> String a -> String a #

min :: String a -> String a -> String a #

Show a => Show (String a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> String a -> ShowS #

show :: String a -> String0 #

showList :: [String a] -> ShowS #

Generic (String a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (String a) :: Type -> Type #

Methods

from :: String a -> Rep (String a) x #

to :: Rep (String a) x -> String a #

Unmarshal a => Unmarshal (String a) Source # 
Instance details

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 (String a)

SymbolMatching (String a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (String a) -> Node -> Bool

showFailure :: Proxy (String a) -> Node -> String0

type Rep (String a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (String a) = D1 (MetaData "String" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "String" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either (EscapeSequence a) (Interpolation a)])))

data Interpolation a Source #

Instances
Eq a => Eq (Interpolation a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (Interpolation a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (Interpolation a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (Interpolation a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Interpolation a) :: Type -> Type #

Unmarshal a => Unmarshal (Interpolation a) Source # 
Instance details

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 (Interpolation a)

SymbolMatching (Interpolation a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Interpolation a) -> Node -> Bool

showFailure :: Proxy (Interpolation a) -> Node -> String

type Rep (Interpolation a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Interpolation a) = D1 (MetaData "Interpolation" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "Interpolation" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Either (Expression a) (Either (FormatSpecifier a) (TypeConversion a)))))))

data FormatSpecifier a Source #

Constructors

FormatSpecifier 

Fields

Instances
Eq a => Eq (FormatSpecifier a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (FormatSpecifier a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (FormatSpecifier a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (FormatSpecifier a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (FormatSpecifier a) :: Type -> Type #

Unmarshal a => Unmarshal (FormatSpecifier a) Source # 
Instance details

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 (FormatSpecifier a)

SymbolMatching (FormatSpecifier a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (FormatSpecifier a) -> Node -> Bool

showFailure :: Proxy (FormatSpecifier a) -> Node -> String

type Rep (FormatSpecifier a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (FormatSpecifier a) = D1 (MetaData "FormatSpecifier" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "FormatSpecifier" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FormatExpression a])))

data FormatExpression a Source #

Constructors

FormatExpression 

Fields

Instances
Eq a => Eq (FormatExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (FormatExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (FormatExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (FormatExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (FormatExpression a) :: Type -> Type #

Unmarshal a => Unmarshal (FormatExpression a) Source # 
Instance details

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 (FormatExpression a)

SymbolMatching (FormatExpression a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (FormatExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (FormatExpression a) = D1 (MetaData "FormatExpression" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "FormatExpression" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a))))

data SetComprehension a Source #

Constructors

SetComprehension 

Fields

Instances
Eq a => Eq (SetComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (SetComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (SetComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (SetComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (SetComprehension a) :: Type -> Type #

Unmarshal a => Unmarshal (SetComprehension a) Source # 
Instance details

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 (SetComprehension a)

SymbolMatching (SetComprehension a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (SetComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (SetComprehension a) = D1 (MetaData "SetComprehension" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "SetComprehension" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a)) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Either (ForInClause a) (IfClause a)))))))

data IfClause a Source #

Constructors

IfClause 

Fields

Instances
Eq a => Eq (IfClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: IfClause a -> IfClause a -> Bool #

(/=) :: IfClause a -> IfClause a -> Bool #

Ord a => Ord (IfClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: IfClause a -> IfClause a -> Ordering #

(<) :: IfClause a -> IfClause a -> Bool #

(<=) :: IfClause a -> IfClause a -> Bool #

(>) :: IfClause a -> IfClause a -> Bool #

(>=) :: IfClause a -> IfClause a -> Bool #

max :: IfClause a -> IfClause a -> IfClause a #

min :: IfClause a -> IfClause a -> IfClause a #

Show a => Show (IfClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> IfClause a -> ShowS #

show :: IfClause a -> String #

showList :: [IfClause a] -> ShowS #

Generic (IfClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (IfClause a) :: Type -> Type #

Methods

from :: IfClause a -> Rep (IfClause a) x #

to :: Rep (IfClause a) x -> IfClause a #

Unmarshal a => Unmarshal (IfClause a) Source # 
Instance details

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 (IfClause a)

SymbolMatching (IfClause a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (IfClause a) -> Node -> Bool

showFailure :: Proxy (IfClause a) -> Node -> String

type Rep (IfClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (IfClause a) = D1 (MetaData "IfClause" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "IfClause" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a))))

data ForInClause a Source #

Constructors

ForInClause 

Fields

Instances
Eq a => Eq (ForInClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ForInClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ForInClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ForInClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ForInClause a) :: Type -> Type #

Methods

from :: ForInClause a -> Rep (ForInClause a) x #

to :: Rep (ForInClause a) x -> ForInClause a #

Unmarshal a => Unmarshal (ForInClause a) Source # 
Instance details

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 (ForInClause a)

SymbolMatching (ForInClause a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (ForInClause a) -> Node -> Bool

showFailure :: Proxy (ForInClause a) -> Node -> String

type Rep (ForInClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ForInClause a) = D1 (MetaData "ForInClause" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ForInClause" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "left") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Variables a)) :*: S1 (MetaSel (Just "right") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Either (AnonymousComma a) (Either (Expression a) (Lambda a))))))))

data Variables a Source #

Constructors

Variables 
Instances
Eq a => Eq (Variables a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Variables a -> Variables a -> Bool #

(/=) :: Variables a -> Variables a -> Bool #

Ord a => Ord (Variables a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (Variables a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (Variables a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Variables a) :: Type -> Type #

Methods

from :: Variables a -> Rep (Variables a) x #

to :: Rep (Variables a) x -> Variables a #

Unmarshal a => Unmarshal (Variables a) Source # 
Instance details

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 (Variables a)

SymbolMatching (Variables a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Variables a) -> Node -> Bool

showFailure :: Proxy (Variables a) -> Node -> String

type Rep (Variables a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Variables a) = D1 (MetaData "Variables" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "Variables" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (PrimaryExpression a)))))

data Set a Source #

Constructors

Set 

Fields

Instances
Eq a => Eq (Set a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Set a -> Set a -> Bool #

(/=) :: Set a -> Set a -> Bool #

Ord a => Ord (Set a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Set a -> Set a -> Ordering #

(<) :: Set a -> Set a -> Bool #

(<=) :: Set a -> Set a -> Bool #

(>) :: Set a -> Set a -> Bool #

(>=) :: Set a -> Set a -> Bool #

max :: Set a -> Set a -> Set a #

min :: Set a -> Set a -> Set a #

Show a => Show (Set a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Set a -> ShowS #

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Generic (Set a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Set a) :: Type -> Type #

Methods

from :: Set a -> Rep (Set a) x #

to :: Rep (Set a) x -> Set a #

Unmarshal a => Unmarshal (Set a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Set a) -> Node -> Bool

showFailure :: Proxy (Set a) -> Node -> String

type Rep (Set a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Set a) = D1 (MetaData "Set" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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
Eq a => Eq (ParenthesizedExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ParenthesizedExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ParenthesizedExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ParenthesizedExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ParenthesizedExpression a) :: Type -> Type #

Unmarshal a => Unmarshal (ParenthesizedExpression a) Source # 
Instance details

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 (ParenthesizedExpression a)

SymbolMatching (ParenthesizedExpression a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ParenthesizedExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ParenthesizedExpression a) = D1 (MetaData "ParenthesizedExpression" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ParenthesizedExpression" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either (Expression a) (Yield a)))))

data ListComprehension a Source #

Constructors

ListComprehension 

Fields

Instances
Eq a => Eq (ListComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ListComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ListComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ListComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ListComprehension a) :: Type -> Type #

Unmarshal a => Unmarshal (ListComprehension a) Source # 
Instance details

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 (ListComprehension a)

SymbolMatching (ListComprehension a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ListComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ListComprehension a) = D1 (MetaData "ListComprehension" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ListComprehension" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a)) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Either (ForInClause a) (IfClause a)))))))

data List a Source #

Constructors

List 

Fields

Instances
Eq a => Eq (List a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: List a -> List a -> Bool #

(/=) :: List a -> List a -> Bool #

Ord a => Ord (List a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: List a -> List a -> Ordering #

(<) :: List a -> List a -> Bool #

(<=) :: List a -> List a -> Bool #

(>) :: List a -> List a -> Bool #

(>=) :: List a -> List a -> Bool #

max :: List a -> List a -> List a #

min :: List a -> List a -> List a #

Show a => Show (List a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> List a -> ShowS #

show :: List a -> String #

showList :: [List a] -> ShowS #

Generic (List a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (List a) :: Type -> Type #

Methods

from :: List a -> Rep (List a) x #

to :: Rep (List a) x -> List a #

Unmarshal a => Unmarshal (List a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (List a) -> Node -> Bool

showFailure :: Proxy (List a) -> Node -> String

type Rep (List a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (List a) = D1 (MetaData "List" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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
Eq a => Eq (GeneratorExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (GeneratorExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (GeneratorExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (GeneratorExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (GeneratorExpression a) :: Type -> Type #

Unmarshal a => Unmarshal (GeneratorExpression a) Source # 
Instance details

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 (GeneratorExpression a)

SymbolMatching (GeneratorExpression a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (GeneratorExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (GeneratorExpression a) = D1 (MetaData "GeneratorExpression" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "GeneratorExpression" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a)) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Either (ForInClause a) (IfClause a)))))))

data DictionaryComprehension a Source #

Constructors

DictionaryComprehension 

Fields

Instances
Eq a => Eq (DictionaryComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (DictionaryComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (DictionaryComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (DictionaryComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (DictionaryComprehension a) :: Type -> Type #

Unmarshal a => Unmarshal (DictionaryComprehension a) Source # 
Instance details

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 (DictionaryComprehension a)

SymbolMatching (DictionaryComprehension a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (DictionaryComprehension a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (DictionaryComprehension a) = D1 (MetaData "DictionaryComprehension" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "DictionaryComprehension" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Pair a)) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Either (ForInClause a) (IfClause a)))))))

data Pair a Source #

Constructors

Pair 

Fields

Instances
Eq a => Eq (Pair a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Pair a -> Pair a -> Bool #

(/=) :: Pair a -> Pair a -> Bool #

Ord a => Ord (Pair a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Pair a -> Pair a -> Ordering #

(<) :: Pair a -> Pair a -> Bool #

(<=) :: Pair a -> Pair a -> Bool #

(>) :: Pair a -> Pair a -> Bool #

(>=) :: Pair a -> Pair a -> Bool #

max :: Pair a -> Pair a -> Pair a #

min :: Pair a -> Pair a -> Pair a #

Show a => Show (Pair a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Pair a -> ShowS #

show :: Pair a -> String #

showList :: [Pair a] -> ShowS #

Generic (Pair a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Pair a) :: Type -> Type #

Methods

from :: Pair a -> Rep (Pair a) x #

to :: Rep (Pair a) x -> Pair a #

Unmarshal a => Unmarshal (Pair a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Pair a) -> Node -> Bool

showFailure :: Proxy (Pair a) -> Node -> String

type Rep (Pair a) Source # 
Instance details

Defined in TreeSitter.Python.AST

data Dictionary a Source #

Constructors

Dictionary 

Fields

Instances
Eq a => Eq (Dictionary a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Dictionary a -> Dictionary a -> Bool #

(/=) :: Dictionary a -> Dictionary a -> Bool #

Ord a => Ord (Dictionary a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (Dictionary a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (Dictionary a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Dictionary a) :: Type -> Type #

Methods

from :: Dictionary a -> Rep (Dictionary a) x #

to :: Rep (Dictionary a) x -> Dictionary a #

Unmarshal a => Unmarshal (Dictionary a) Source # 
Instance details

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 (Dictionary a)

SymbolMatching (Dictionary a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Dictionary a) -> Node -> Bool

showFailure :: Proxy (Dictionary a) -> Node -> String

type Rep (Dictionary a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Dictionary a) = D1 (MetaData "Dictionary" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "Dictionary" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either (DictionarySplat a) (Pair a)])))

data ConcatenatedString a Source #

Constructors

ConcatenatedString 

Fields

Instances
Eq a => Eq (ConcatenatedString a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ConcatenatedString a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ConcatenatedString a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ConcatenatedString a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ConcatenatedString a) :: Type -> Type #

Unmarshal a => Unmarshal (ConcatenatedString a) Source # 
Instance details

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 (ConcatenatedString a)

SymbolMatching (ConcatenatedString a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ConcatenatedString a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ConcatenatedString a) = D1 (MetaData "ConcatenatedString" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ConcatenatedString" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (String a)))))

data Call a Source #

Constructors

Call 
Instances
Eq a => Eq (Call a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Call a -> Call a -> Bool #

(/=) :: Call a -> Call a -> Bool #

Ord a => Ord (Call a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Call a -> Call a -> Ordering #

(<) :: Call a -> Call a -> Bool #

(<=) :: Call a -> Call a -> Bool #

(>) :: Call a -> Call a -> Bool #

(>=) :: Call a -> Call a -> Bool #

max :: Call a -> Call a -> Call a #

min :: Call a -> Call a -> Call a #

Show a => Show (Call a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Call a -> ShowS #

show :: Call a -> String #

showList :: [Call a] -> ShowS #

Generic (Call a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Call a) :: Type -> Type #

Methods

from :: Call a -> Rep (Call a) x #

to :: Rep (Call a) x -> Call a #

Unmarshal a => Unmarshal (Call a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Call a) -> Node -> Bool

showFailure :: Proxy (Call a) -> Node -> String

type Rep (Call a) Source # 
Instance details

Defined in TreeSitter.Python.AST

data ArgumentList a Source #

Constructors

ArgumentList 
Instances
Eq a => Eq (ArgumentList a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ArgumentList a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ArgumentList a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ArgumentList a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ArgumentList a) :: Type -> Type #

Methods

from :: ArgumentList a -> Rep (ArgumentList a) x #

to :: Rep (ArgumentList a) x -> ArgumentList a #

Unmarshal a => Unmarshal (ArgumentList a) Source # 
Instance details

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 (ArgumentList a)

SymbolMatching (ArgumentList a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (ArgumentList a) -> Node -> Bool

showFailure :: Proxy (ArgumentList a) -> Node -> String

type Rep (ArgumentList a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ArgumentList a) = D1 (MetaData "ArgumentList" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ArgumentList" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either (Expression a) (Either (DictionarySplat a) (Either (KeywordArgument a) (ListSplat a)))])))

data KeywordArgument a Source #

Constructors

KeywordArgument 

Fields

Instances
Eq a => Eq (KeywordArgument a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (KeywordArgument a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (KeywordArgument a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (KeywordArgument a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (KeywordArgument a) :: Type -> Type #

Unmarshal a => Unmarshal (KeywordArgument a) Source # 
Instance details

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 (KeywordArgument a)

SymbolMatching (KeywordArgument a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (KeywordArgument a) -> Node -> Bool

showFailure :: Proxy (KeywordArgument a) -> Node -> String

type Rep (KeywordArgument a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (KeywordArgument a) = D1 (MetaData "KeywordArgument" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "KeywordArgument" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "value") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a)) :*: S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Identifier a)))))

data BinaryOperator a Source #

Instances
Eq a => Eq (BinaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (BinaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (BinaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (BinaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (BinaryOperator a) :: Type -> Type #

Unmarshal a => Unmarshal (BinaryOperator a) Source # 
Instance details

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 (BinaryOperator a)

SymbolMatching (BinaryOperator a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (BinaryOperator a) -> Node -> Bool

showFailure :: Proxy (BinaryOperator a) -> Node -> String

type Rep (BinaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

data Attribute a Source #

Constructors

Attribute 
Instances
Eq a => Eq (Attribute a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Attribute a -> Attribute a -> Bool #

(/=) :: Attribute a -> Attribute a -> Bool #

Ord a => Ord (Attribute a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (Attribute a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (Attribute a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Attribute a) :: Type -> Type #

Methods

from :: Attribute a -> Rep (Attribute a) x #

to :: Rep (Attribute a) x -> Attribute a #

Unmarshal a => Unmarshal (Attribute a) Source # 
Instance details

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 (Attribute a)

SymbolMatching (Attribute a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Attribute a) -> Node -> Bool

showFailure :: Proxy (Attribute a) -> Node -> String

type Rep (Attribute a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Attribute a) = D1 (MetaData "Attribute" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "Attribute" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Either (PrimaryExpression a) (Identifier a))))))

data WithItem a Source #

Constructors

WithItem 

Fields

Instances
Eq a => Eq (WithItem a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: WithItem a -> WithItem a -> Bool #

(/=) :: WithItem a -> WithItem a -> Bool #

Ord a => Ord (WithItem a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: WithItem a -> WithItem a -> Ordering #

(<) :: WithItem a -> WithItem a -> Bool #

(<=) :: WithItem a -> WithItem a -> Bool #

(>) :: WithItem a -> WithItem a -> Bool #

(>=) :: WithItem a -> WithItem a -> Bool #

max :: WithItem a -> WithItem a -> WithItem a #

min :: WithItem a -> WithItem a -> WithItem a #

Show a => Show (WithItem a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> WithItem a -> ShowS #

show :: WithItem a -> String #

showList :: [WithItem a] -> ShowS #

Generic (WithItem a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (WithItem a) :: Type -> Type #

Methods

from :: WithItem a -> Rep (WithItem a) x #

to :: Rep (WithItem a) x -> WithItem a #

Unmarshal a => Unmarshal (WithItem a) Source # 
Instance details

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 (WithItem a)

SymbolMatching (WithItem a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (WithItem a) -> Node -> Bool

showFailure :: Proxy (WithItem a) -> Node -> String

type Rep (WithItem a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (WithItem a) = D1 (MetaData "WithItem" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "WithItem" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "value") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a)) :*: S1 (MetaSel (Just "alias") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Expression a))))))

data ReturnStatement a Source #

Constructors

ReturnStatement 

Fields

Instances
Eq a => Eq (ReturnStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ReturnStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ReturnStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ReturnStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ReturnStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (ReturnStatement a) Source # 
Instance details

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 (ReturnStatement a)

SymbolMatching (ReturnStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (ReturnStatement a) -> Node -> Bool

showFailure :: Proxy (ReturnStatement a) -> Node -> String

type Rep (ReturnStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ReturnStatement a) = D1 (MetaData "ReturnStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ReturnStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ExpressionList a)))))

data RaiseStatement a Source #

Constructors

RaiseStatement 

Fields

Instances
Eq a => Eq (RaiseStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (RaiseStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (RaiseStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (RaiseStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (RaiseStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (RaiseStatement a) Source # 
Instance details

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 (RaiseStatement a)

SymbolMatching (RaiseStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (RaiseStatement a) -> Node -> Bool

showFailure :: Proxy (RaiseStatement a) -> Node -> String

type Rep (RaiseStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (RaiseStatement a) = D1 (MetaData "RaiseStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "RaiseStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "cause") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ExpressionList a))))))

data DeleteStatement a Source #

Constructors

DeleteStatement 

Fields

Instances
Eq a => Eq (DeleteStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (DeleteStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (DeleteStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (DeleteStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (DeleteStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (DeleteStatement a) Source # 
Instance details

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 (DeleteStatement a)

SymbolMatching (DeleteStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (DeleteStatement a) -> Node -> Bool

showFailure :: Proxy (DeleteStatement a) -> Node -> String

type Rep (DeleteStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (DeleteStatement a) = D1 (MetaData "DeleteStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "DeleteStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ExpressionList a))))

data Assignment a Source #

Constructors

Assignment 
Instances
Eq a => Eq (Assignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Assignment a -> Assignment a -> Bool #

(/=) :: Assignment a -> Assignment a -> Bool #

Ord a => Ord (Assignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (Assignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (Assignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Assignment a) :: Type -> Type #

Methods

from :: Assignment a -> Rep (Assignment a) x #

to :: Rep (Assignment a) x -> Assignment a #

Unmarshal a => Unmarshal (Assignment a) Source # 
Instance details

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 (Assignment a)

SymbolMatching (Assignment a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Assignment a) -> Node -> Bool

showFailure :: Proxy (Assignment a) -> Node -> String

type Rep (Assignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

data AugmentedAssignment a Source #

Instances
Eq a => Eq (AugmentedAssignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AugmentedAssignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AugmentedAssignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AugmentedAssignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AugmentedAssignment a) :: Type -> Type #

Unmarshal a => Unmarshal (AugmentedAssignment a) Source # 
Instance details

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 (AugmentedAssignment a)

SymbolMatching (AugmentedAssignment a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AugmentedAssignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AugmentedAssignment a) = D1 (MetaData "AugmentedAssignment" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "AugmentedAssignment" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "left") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ExpressionList a)) :*: S1 (MetaSel (Just "right") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either (Assignment a) (Either (AugmentedAssignment a) (Either (ExpressionList a) (Yield a))))))))

data ExpressionStatement a Source #

Instances
Eq a => Eq (ExpressionStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ExpressionStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ExpressionStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ExpressionStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ExpressionStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (ExpressionStatement a) Source # 
Instance details

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 (ExpressionStatement a)

SymbolMatching (ExpressionStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ExpressionStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ExpressionStatement a) = D1 (MetaData "ExpressionStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ExpressionStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Either (Expression a) (Either (Assignment a) (Either (AugmentedAssignment a) (Yield a))))))))

data ExecStatement a Source #

Constructors

ExecStatement 

Fields

Instances
Eq a => Eq (ExecStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ExecStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ExecStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ExecStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ExecStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (ExecStatement a) Source # 
Instance details

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 (ExecStatement a)

SymbolMatching (ExecStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (ExecStatement a) -> Node -> Bool

showFailure :: Proxy (ExecStatement a) -> Node -> String

type Rep (ExecStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ExecStatement a) = D1 (MetaData "ExecStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ExecStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "code") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (String a)) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Expression a]))))

data Parameters a Source #

Constructors

Parameters 

Fields

Instances
Eq a => Eq (Parameters a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Parameters a -> Parameters a -> Bool #

(/=) :: Parameters a -> Parameters a -> Bool #

Ord a => Ord (Parameters a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (Parameters a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (Parameters a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Parameters a) :: Type -> Type #

Methods

from :: Parameters a -> Rep (Parameters a) x #

to :: Rep (Parameters a) x -> Parameters a #

Unmarshal a => Unmarshal (Parameters a) Source # 
Instance details

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 (Parameters a)

SymbolMatching (Parameters a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Parameters a) -> Node -> Bool

showFailure :: Proxy (Parameters a) -> Node -> String

type Rep (Parameters a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Parameters a) = D1 (MetaData "Parameters" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "Parameters" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Parameter a])))

data Chevron a Source #

Constructors

Chevron 

Fields

Instances
Eq a => Eq (Chevron a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Chevron a -> Chevron a -> Bool #

(/=) :: Chevron a -> Chevron a -> Bool #

Ord a => Ord (Chevron a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Chevron a -> Chevron a -> Ordering #

(<) :: Chevron a -> Chevron a -> Bool #

(<=) :: Chevron a -> Chevron a -> Bool #

(>) :: Chevron a -> Chevron a -> Bool #

(>=) :: Chevron a -> Chevron a -> Bool #

max :: Chevron a -> Chevron a -> Chevron a #

min :: Chevron a -> Chevron a -> Chevron a #

Show a => Show (Chevron a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Chevron a -> ShowS #

show :: Chevron a -> String #

showList :: [Chevron a] -> ShowS #

Generic (Chevron a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Chevron a) :: Type -> Type #

Methods

from :: Chevron a -> Rep (Chevron a) x #

to :: Rep (Chevron a) x -> Chevron a #

Unmarshal a => Unmarshal (Chevron a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Chevron a) -> Node -> Bool

showFailure :: Proxy (Chevron a) -> Node -> String

type Rep (Chevron a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Chevron a) = D1 (MetaData "Chevron" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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
Eq a => Eq (PrintStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (PrintStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (PrintStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (PrintStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (PrintStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (PrintStatement a) Source # 
Instance details

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 (PrintStatement a)

SymbolMatching (PrintStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (PrintStatement a) -> Node -> Bool

showFailure :: Proxy (PrintStatement a) -> Node -> String

type Rep (PrintStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (PrintStatement a) = D1 (MetaData "PrintStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "PrintStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "argument") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Expression a]) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Chevron a]))))

data AssertStatement a Source #

Constructors

AssertStatement 

Fields

Instances
Eq a => Eq (AssertStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AssertStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AssertStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AssertStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AssertStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (AssertStatement a) Source # 
Instance details

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 (AssertStatement a)

SymbolMatching (AssertStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AssertStatement a) -> Node -> Bool

showFailure :: Proxy (AssertStatement a) -> Node -> String

type Rep (AssertStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AssertStatement a) = D1 (MetaData "AssertStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "AssertStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Expression a)))))

data SimpleStatement a Source #

Instances
Eq a => Eq (SimpleStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (SimpleStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (SimpleStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (SimpleStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (SimpleStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (SimpleStatement a) Source # 
Instance details

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 (SimpleStatement a)

SymbolMatching (SimpleStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (SimpleStatement a) -> Node -> Bool

showFailure :: Proxy (SimpleStatement a) -> Node -> String

type Rep (SimpleStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (SimpleStatement a) = D1 (MetaData "SimpleStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (((C1 (MetaCons "AssertStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AssertStatement a))) :+: (C1 (MetaCons "BreakStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (BreakStatement a))) :+: C1 (MetaCons "ContinueStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ContinueStatement a))))) :+: ((C1 (MetaCons "DeleteStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DeleteStatement a))) :+: C1 (MetaCons "ExecStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ExecStatement a)))) :+: (C1 (MetaCons "ExpressionStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ExpressionStatement a))) :+: C1 (MetaCons "FutureImportStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (FutureImportStatement a)))))) :+: (((C1 (MetaCons "GlobalStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (GlobalStatement a))) :+: C1 (MetaCons "ImportFromStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ImportFromStatement a)))) :+: (C1 (MetaCons "ImportStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ImportStatement a))) :+: C1 (MetaCons "NonlocalStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonlocalStatement a))))) :+: ((C1 (MetaCons "PassStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PassStatement a))) :+: C1 (MetaCons "PrintStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PrintStatement a)))) :+: (C1 (MetaCons "RaiseStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RaiseStatement a))) :+: C1 (MetaCons "ReturnStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ReturnStatement a)))))))

data Decorator a Source #

Constructors

Decorator 

Fields

Instances
Eq a => Eq (Decorator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Decorator a -> Decorator a -> Bool #

(/=) :: Decorator a -> Decorator a -> Bool #

Ord a => Ord (Decorator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (Decorator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (Decorator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Decorator a) :: Type -> Type #

Methods

from :: Decorator a -> Rep (Decorator a) x #

to :: Rep (Decorator a) x -> Decorator a #

Unmarshal a => Unmarshal (Decorator a) Source # 
Instance details

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 (Decorator a)

SymbolMatching (Decorator a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Decorator a) -> Node -> Bool

showFailure :: Proxy (Decorator a) -> Node -> String

type Rep (Decorator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Decorator a) = D1 (MetaData "Decorator" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "Decorator" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "arguments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ArgumentList a))) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DottedName a)))))

data ClassDefinition a Source #

Constructors

ClassDefinition 

Fields

Instances
Eq a => Eq (ClassDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ClassDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ClassDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ClassDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ClassDefinition a) :: Type -> Type #

Unmarshal a => Unmarshal (ClassDefinition a) Source # 
Instance details

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 (ClassDefinition a)

SymbolMatching (ClassDefinition a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (ClassDefinition a) -> Node -> Bool

showFailure :: Proxy (ClassDefinition a) -> Node -> String

type Rep (ClassDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

data Block a Source #

Constructors

Block 

Fields

Instances
Eq a => Eq (Block a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Block a -> Block a -> Bool #

(/=) :: Block a -> Block a -> Bool #

Ord a => Ord (Block a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Block a -> Block a -> Ordering #

(<) :: Block a -> Block a -> Bool #

(<=) :: Block a -> Block a -> Bool #

(>) :: Block a -> Block a -> Bool #

(>=) :: Block a -> Block a -> Bool #

max :: Block a -> Block a -> Block a #

min :: Block a -> Block a -> Block a #

Show a => Show (Block a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Block a -> ShowS #

show :: Block a -> String #

showList :: [Block a] -> ShowS #

Generic (Block a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Block a) :: Type -> Type #

Methods

from :: Block a -> Rep (Block a) x #

to :: Rep (Block a) x -> Block a #

Unmarshal a => Unmarshal (Block a) Source # 
Instance details

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 (Block a)

SymbolMatching (Block a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Block a) -> Node -> Bool

showFailure :: Proxy (Block a) -> Node -> String

type Rep (Block a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Block a) = D1 (MetaData "Block" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "Block" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either (CompoundStatement a) (SimpleStatement a)])))

data CompoundStatement a Source #

Instances
Eq a => Eq (CompoundStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (CompoundStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (CompoundStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (CompoundStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (CompoundStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (CompoundStatement a) Source # 
Instance details

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 (CompoundStatement a)

SymbolMatching (CompoundStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (CompoundStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (CompoundStatement a) = D1 (MetaData "CompoundStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (((C1 (MetaCons "ClassDefinitionCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ClassDefinition a))) :+: C1 (MetaCons "DecoratedDefinitionCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DecoratedDefinition a)))) :+: (C1 (MetaCons "ForStatementCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ForStatement a))) :+: C1 (MetaCons "FunctionDefinitionCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (FunctionDefinition a))))) :+: ((C1 (MetaCons "IfStatementCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IfStatement a))) :+: C1 (MetaCons "TryStatementCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (TryStatement a)))) :+: (C1 (MetaCons "WhileStatementCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (WhileStatement a))) :+: C1 (MetaCons "WithStatementCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (WithStatement a))))))

data WithStatement a Source #

Constructors

WithStatement 

Fields

Instances
Eq a => Eq (WithStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (WithStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (WithStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (WithStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (WithStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (WithStatement a) Source # 
Instance details

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 (WithStatement a)

SymbolMatching (WithStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (WithStatement a) -> Node -> Bool

showFailure :: Proxy (WithStatement a) -> Node -> String

type Rep (WithStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (WithStatement a) = D1 (MetaData "WithStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "WithStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Block a)) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (WithItem a))))))

data WhileStatement a Source #

Constructors

WhileStatement 

Fields

Instances
Eq a => Eq (WhileStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (WhileStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (WhileStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (WhileStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (WhileStatement a) :: Type -> Type #

Unmarshal a => Unmarshal (WhileStatement a) Source # 
Instance details

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 (WhileStatement a)

SymbolMatching (WhileStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (WhileStatement a) -> Node -> Bool

showFailure :: Proxy (WhileStatement a) -> Node -> String

type Rep (WhileStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (WhileStatement a) = D1 (MetaData "WhileStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "WhileStatement" PrefixI True) ((S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "alternative") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ElseClause a)))) :*: (S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Block a)) :*: S1 (MetaSel (Just "condition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a)))))

data ElseClause a Source #

Constructors

ElseClause 

Fields

Instances
Eq a => Eq (ElseClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: ElseClause a -> ElseClause a -> Bool #

(/=) :: ElseClause a -> ElseClause a -> Bool #

Ord a => Ord (ElseClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ElseClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ElseClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ElseClause a) :: Type -> Type #

Methods

from :: ElseClause a -> Rep (ElseClause a) x #

to :: Rep (ElseClause a) x -> ElseClause a #

Unmarshal a => Unmarshal (ElseClause a) Source # 
Instance details

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 (ElseClause a)

SymbolMatching (ElseClause a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (ElseClause a) -> Node -> Bool

showFailure :: Proxy (ElseClause a) -> Node -> String

type Rep (ElseClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ElseClause a) = D1 (MetaData "ElseClause" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ElseClause" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Block a))))

data TryStatement a Source #

Constructors

TryStatement 
Instances
Eq a => Eq (TryStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (TryStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (TryStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (TryStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (TryStatement a) :: Type -> Type #

Methods

from :: TryStatement a -> Rep (TryStatement a) x #

to :: Rep (TryStatement a) x -> TryStatement a #

Unmarshal a => Unmarshal (TryStatement a) Source # 
Instance details

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 (TryStatement a)

SymbolMatching (TryStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (TryStatement a) -> Node -> Bool

showFailure :: Proxy (TryStatement a) -> Node -> String

type Rep (TryStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (TryStatement a) = D1 (MetaData "TryStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "TryStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Block a)) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Either (ElseClause a) (Either (ExceptClause a) (FinallyClause a))))))))

data FinallyClause a Source #

Constructors

FinallyClause 

Fields

Instances
Eq a => Eq (FinallyClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (FinallyClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (FinallyClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (FinallyClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (FinallyClause a) :: Type -> Type #

Unmarshal a => Unmarshal (FinallyClause a) Source # 
Instance details

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 (FinallyClause a)

SymbolMatching (FinallyClause a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (FinallyClause a) -> Node -> Bool

showFailure :: Proxy (FinallyClause a) -> Node -> String

type Rep (FinallyClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (FinallyClause a) = D1 (MetaData "FinallyClause" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "FinallyClause" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Block a))))

data ExceptClause a Source #

Constructors

ExceptClause 

Fields

Instances
Eq a => Eq (ExceptClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ExceptClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ExceptClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ExceptClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ExceptClause a) :: Type -> Type #

Methods

from :: ExceptClause a -> Rep (ExceptClause a) x #

to :: Rep (ExceptClause a) x -> ExceptClause a #

Unmarshal a => Unmarshal (ExceptClause a) Source # 
Instance details

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 (ExceptClause a)

SymbolMatching (ExceptClause a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (ExceptClause a) -> Node -> Bool

showFailure :: Proxy (ExceptClause a) -> Node -> String

type Rep (ExceptClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ExceptClause a) = D1 (MetaData "ExceptClause" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ExceptClause" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Either (Expression a) (Block a))))))

data IfStatement a Source #

Constructors

IfStatement 

Fields

Instances
Eq a => Eq (IfStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (IfStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (IfStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (IfStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (IfStatement a) :: Type -> Type #

Methods

from :: IfStatement a -> Rep (IfStatement a) x #

to :: Rep (IfStatement a) x -> IfStatement a #

Unmarshal a => Unmarshal (IfStatement a) Source # 
Instance details

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 (IfStatement a)

SymbolMatching (IfStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (IfStatement a) -> Node -> Bool

showFailure :: Proxy (IfStatement a) -> Node -> String

type Rep (IfStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (IfStatement a) = D1 (MetaData "IfStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "IfStatement" PrefixI True) ((S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "alternative") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either (ElifClause a) (ElseClause a)])) :*: (S1 (MetaSel (Just "consequence") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Block a)) :*: S1 (MetaSel (Just "condition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a)))))

data ElifClause a Source #

Constructors

ElifClause 

Fields

Instances
Eq a => Eq (ElifClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: ElifClause a -> ElifClause a -> Bool #

(/=) :: ElifClause a -> ElifClause a -> Bool #

Ord a => Ord (ElifClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ElifClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ElifClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ElifClause a) :: Type -> Type #

Methods

from :: ElifClause a -> Rep (ElifClause a) x #

to :: Rep (ElifClause a) x -> ElifClause a #

Unmarshal a => Unmarshal (ElifClause a) Source # 
Instance details

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 (ElifClause a)

SymbolMatching (ElifClause a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (ElifClause a) -> Node -> Bool

showFailure :: Proxy (ElifClause a) -> Node -> String

type Rep (ElifClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ElifClause a) = D1 (MetaData "ElifClause" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "ElifClause" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "consequence") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Block a)) :*: S1 (MetaSel (Just "condition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a)))))

data FunctionDefinition a Source #

Constructors

FunctionDefinition 

Fields

Instances
Eq a => Eq (FunctionDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (FunctionDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (FunctionDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (FunctionDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (FunctionDefinition a) :: Type -> Type #

Unmarshal a => Unmarshal (FunctionDefinition a) Source # 
Instance details

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 (FunctionDefinition a)

SymbolMatching (FunctionDefinition a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (FunctionDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

data ForStatement a Source #

Constructors

ForStatement 

Fields

Instances
Eq a => Eq (ForStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (ForStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (ForStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (ForStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (ForStatement a) :: Type -> Type #

Methods

from :: ForStatement a -> Rep (ForStatement a) x #

to :: Rep (ForStatement a) x -> ForStatement a #

Unmarshal a => Unmarshal (ForStatement a) Source # 
Instance details

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 (ForStatement a)

SymbolMatching (ForStatement a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (ForStatement a) -> Node -> Bool

showFailure :: Proxy (ForStatement a) -> Node -> String

type Rep (ForStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

data DecoratedDefinition a Source #

Instances
Eq a => Eq (DecoratedDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (DecoratedDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (DecoratedDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (DecoratedDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (DecoratedDefinition a) :: Type -> Type #

Unmarshal a => Unmarshal (DecoratedDefinition a) Source # 
Instance details

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 (DecoratedDefinition a)

SymbolMatching (DecoratedDefinition a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (DecoratedDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (DecoratedDefinition a) = D1 (MetaData "DecoratedDefinition" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "DecoratedDefinition" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "definition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either (ClassDefinition a) (FunctionDefinition a))) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Decorator a))))))

data Module a Source #

Constructors

Module 

Fields

Instances
Eq a => Eq (Module a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Module a -> Module a -> Bool #

(/=) :: Module a -> Module a -> Bool #

Ord a => Ord (Module a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Module a -> Module a -> Ordering #

(<) :: Module a -> Module a -> Bool #

(<=) :: Module a -> Module a -> Bool #

(>) :: Module a -> Module a -> Bool #

(>=) :: Module a -> Module a -> Bool #

max :: Module a -> Module a -> Module a #

min :: Module a -> Module a -> Module a #

Show a => Show (Module a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Module a -> ShowS #

show :: Module a -> String #

showList :: [Module a] -> ShowS #

Generic (Module a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Module a) :: Type -> Type #

Methods

from :: Module a -> Rep (Module a) x #

to :: Rep (Module a) x -> Module a #

Unmarshal a => Unmarshal (Module a) Source # 
Instance details

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 (Module a)

SymbolMatching (Module a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Module a) -> Node -> Bool

showFailure :: Proxy (Module a) -> Node -> String

type Rep (Module a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Module a) = D1 (MetaData "Module" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" False) (C1 (MetaCons "Module" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either (CompoundStatement a) (SimpleStatement a)])))

newtype AnonymousAwait a Source #

Constructors

AnonymousAwait 

Fields

Instances
Eq a => Eq (AnonymousAwait a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Ord a => Ord (AnonymousAwait a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Show a => Show (AnonymousAwait a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Generic (AnonymousAwait a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (AnonymousAwait a) :: Type -> Type #

Unmarshal a => Unmarshal (AnonymousAwait a) Source # 
Instance details

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 (AnonymousAwait a)

SymbolMatching (AnonymousAwait a :: Type) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (AnonymousAwait a) -> Node -> Bool

showFailure :: Proxy (AnonymousAwait a) -> Node -> String

type Rep (AnonymousAwait a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (AnonymousAwait a) = D1 (MetaData "AnonymousAwait" "TreeSitter.Python.AST" "tree-sitter-python-0.4.0.0-inplace" True) (C1 (MetaCons "AnonymousAwait" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data Comment a Source #

Constructors

Comment 

Fields

Instances
Eq a => Eq (Comment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

(==) :: Comment a -> Comment a -> Bool #

(/=) :: Comment a -> Comment a -> Bool #

Ord a => Ord (Comment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

compare :: Comment a -> Comment a -> Ordering #

(<) :: Comment a -> Comment a -> Bool #

(<=) :: Comment a -> Comment a -> Bool #

(>) :: Comment a -> Comment a -> Bool #

(>=) :: Comment a -> Comment a -> Bool #

max :: Comment a -> Comment a -> Comment a #

min :: Comment a -> Comment a -> Comment a #

Show a => Show (Comment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

showsPrec :: Int -> Comment a -> ShowS #

show :: Comment a -> String #

showList :: [Comment a] -> ShowS #

Generic (Comment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep (Comment a) :: Type -> Type #

Methods

from :: Comment a -> Rep (Comment a) x #

to :: Rep (Comment a) x -> Comment a #

Unmarshal a => Unmarshal (Comment a) Source # 
Instance details

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 # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy (Comment a) -> Node -> Bool

showFailure :: Proxy (Comment a) -> Node -> String

type Rep (Comment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Comment a) = D1 (MetaData "Comment" "TreeSitter.Python.AST" "tree-sitter-python-0.4.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)))