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

Safe HaskellNone
LanguageHaskell2010

TreeSitter.Python.AST

Documentation

data BreakStatement a Source #

Constructors

BreakStatement 

Fields

Instances
Functor BreakStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> BreakStatement a -> BreakStatement b #

(<$) :: a -> BreakStatement b -> BreakStatement a #

Foldable BreakStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => BreakStatement m -> m #

foldMap :: Monoid m => (a -> m) -> BreakStatement a -> m #

foldr :: (a -> b -> b) -> b -> BreakStatement a -> b #

foldr' :: (a -> b -> b) -> b -> BreakStatement a -> b #

foldl :: (b -> a -> b) -> b -> BreakStatement a -> b #

foldl' :: (b -> a -> b) -> b -> BreakStatement a -> b #

foldr1 :: (a -> a -> a) -> BreakStatement a -> a #

foldl1 :: (a -> a -> a) -> BreakStatement a -> a #

toList :: BreakStatement a -> [a] #

null :: BreakStatement a -> Bool #

length :: BreakStatement a -> Int #

elem :: Eq a => a -> BreakStatement a -> Bool #

maximum :: Ord a => BreakStatement a -> a #

minimum :: Ord a => BreakStatement a -> a #

sum :: Num a => BreakStatement a -> a #

product :: Num a => BreakStatement a -> a #

Traversable BreakStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> BreakStatement a -> f (BreakStatement b) #

sequenceA :: Applicative f => BreakStatement (f a) -> f (BreakStatement a) #

mapM :: Monad m => (a -> m b) -> BreakStatement a -> m (BreakStatement b) #

sequence :: Monad m => BreakStatement (m a) -> m (BreakStatement a) #

SymbolMatching BreakStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal BreakStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (BreakStatement a)

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 #

Generic1 BreakStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 BreakStatement :: k -> Type #

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.5.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)))
type Rep1 BreakStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

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

data ContinueStatement a Source #

Constructors

ContinueStatement 

Fields

Instances
Functor ContinueStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable ContinueStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ContinueStatement m -> m #

foldMap :: Monoid m => (a -> m) -> ContinueStatement a -> m #

foldr :: (a -> b -> b) -> b -> ContinueStatement a -> b #

foldr' :: (a -> b -> b) -> b -> ContinueStatement a -> b #

foldl :: (b -> a -> b) -> b -> ContinueStatement a -> b #

foldl' :: (b -> a -> b) -> b -> ContinueStatement a -> b #

foldr1 :: (a -> a -> a) -> ContinueStatement a -> a #

foldl1 :: (a -> a -> a) -> ContinueStatement a -> a #

toList :: ContinueStatement a -> [a] #

null :: ContinueStatement a -> Bool #

length :: ContinueStatement a -> Int #

elem :: Eq a => a -> ContinueStatement a -> Bool #

maximum :: Ord a => ContinueStatement a -> a #

minimum :: Ord a => ContinueStatement a -> a #

sum :: Num a => ContinueStatement a -> a #

product :: Num a => ContinueStatement a -> a #

Traversable ContinueStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ContinueStatement a -> f (ContinueStatement b) #

sequenceA :: Applicative f => ContinueStatement (f a) -> f (ContinueStatement a) #

mapM :: Monad m => (a -> m b) -> ContinueStatement a -> m (ContinueStatement b) #

sequence :: Monad m => ContinueStatement (m a) -> m (ContinueStatement a) #

SymbolMatching ContinueStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ContinueStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ContinueStatement a)

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 #

Generic1 ContinueStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ContinueStatement :: k -> Type #

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.5.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)))
type Rep1 ContinueStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

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

data ImportPrefix a Source #

Constructors

ImportPrefix 

Fields

Instances
Functor ImportPrefix Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> ImportPrefix a -> ImportPrefix b #

(<$) :: a -> ImportPrefix b -> ImportPrefix a #

Foldable ImportPrefix Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ImportPrefix m -> m #

foldMap :: Monoid m => (a -> m) -> ImportPrefix a -> m #

foldr :: (a -> b -> b) -> b -> ImportPrefix a -> b #

foldr' :: (a -> b -> b) -> b -> ImportPrefix a -> b #

foldl :: (b -> a -> b) -> b -> ImportPrefix a -> b #

foldl' :: (b -> a -> b) -> b -> ImportPrefix a -> b #

foldr1 :: (a -> a -> a) -> ImportPrefix a -> a #

foldl1 :: (a -> a -> a) -> ImportPrefix a -> a #

toList :: ImportPrefix a -> [a] #

null :: ImportPrefix a -> Bool #

length :: ImportPrefix a -> Int #

elem :: Eq a => a -> ImportPrefix a -> Bool #

maximum :: Ord a => ImportPrefix a -> a #

minimum :: Ord a => ImportPrefix a -> a #

sum :: Num a => ImportPrefix a -> a #

product :: Num a => ImportPrefix a -> a #

Traversable ImportPrefix Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ImportPrefix a -> f (ImportPrefix b) #

sequenceA :: Applicative f => ImportPrefix (f a) -> f (ImportPrefix a) #

mapM :: Monad m => (a -> m b) -> ImportPrefix a -> m (ImportPrefix b) #

sequence :: Monad m => ImportPrefix (m a) -> m (ImportPrefix a) #

SymbolMatching ImportPrefix Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ImportPrefix Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ImportPrefix a)

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 #

Generic1 ImportPrefix Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ImportPrefix :: k -> Type #

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.5.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)))
type Rep1 ImportPrefix Source # 
Instance details

Defined in TreeSitter.Python.AST

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

data PassStatement a Source #

Constructors

PassStatement 

Fields

Instances
Functor PassStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> PassStatement a -> PassStatement b #

(<$) :: a -> PassStatement b -> PassStatement a #

Foldable PassStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => PassStatement m -> m #

foldMap :: Monoid m => (a -> m) -> PassStatement a -> m #

foldr :: (a -> b -> b) -> b -> PassStatement a -> b #

foldr' :: (a -> b -> b) -> b -> PassStatement a -> b #

foldl :: (b -> a -> b) -> b -> PassStatement a -> b #

foldl' :: (b -> a -> b) -> b -> PassStatement a -> b #

foldr1 :: (a -> a -> a) -> PassStatement a -> a #

foldl1 :: (a -> a -> a) -> PassStatement a -> a #

toList :: PassStatement a -> [a] #

null :: PassStatement a -> Bool #

length :: PassStatement a -> Int #

elem :: Eq a => a -> PassStatement a -> Bool #

maximum :: Ord a => PassStatement a -> a #

minimum :: Ord a => PassStatement a -> a #

sum :: Num a => PassStatement a -> a #

product :: Num a => PassStatement a -> a #

Traversable PassStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> PassStatement a -> f (PassStatement b) #

sequenceA :: Applicative f => PassStatement (f a) -> f (PassStatement a) #

mapM :: Monad m => (a -> m b) -> PassStatement a -> m (PassStatement b) #

sequence :: Monad m => PassStatement (m a) -> m (PassStatement a) #

SymbolMatching PassStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal PassStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (PassStatement a)

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 #

Generic1 PassStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 PassStatement :: k -> Type #

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.5.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)))
type Rep1 PassStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

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

data WildcardImport a Source #

Constructors

WildcardImport 

Fields

Instances
Functor WildcardImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> WildcardImport a -> WildcardImport b #

(<$) :: a -> WildcardImport b -> WildcardImport a #

Foldable WildcardImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => WildcardImport m -> m #

foldMap :: Monoid m => (a -> m) -> WildcardImport a -> m #

foldr :: (a -> b -> b) -> b -> WildcardImport a -> b #

foldr' :: (a -> b -> b) -> b -> WildcardImport a -> b #

foldl :: (b -> a -> b) -> b -> WildcardImport a -> b #

foldl' :: (b -> a -> b) -> b -> WildcardImport a -> b #

foldr1 :: (a -> a -> a) -> WildcardImport a -> a #

foldl1 :: (a -> a -> a) -> WildcardImport a -> a #

toList :: WildcardImport a -> [a] #

null :: WildcardImport a -> Bool #

length :: WildcardImport a -> Int #

elem :: Eq a => a -> WildcardImport a -> Bool #

maximum :: Ord a => WildcardImport a -> a #

minimum :: Ord a => WildcardImport a -> a #

sum :: Num a => WildcardImport a -> a #

product :: Num a => WildcardImport a -> a #

Traversable WildcardImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> WildcardImport a -> f (WildcardImport b) #

sequenceA :: Applicative f => WildcardImport (f a) -> f (WildcardImport a) #

mapM :: Monad m => (a -> m b) -> WildcardImport a -> m (WildcardImport b) #

sequence :: Monad m => WildcardImport (m a) -> m (WildcardImport a) #

SymbolMatching WildcardImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal WildcardImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (WildcardImport a)

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 #

Generic1 WildcardImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 WildcardImport :: k -> Type #

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.5.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)))
type Rep1 WildcardImport Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousImport a Source #

Constructors

AnonymousImport 

Fields

Instances
Functor AnonymousImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousImport a -> AnonymousImport b #

(<$) :: a -> AnonymousImport b -> AnonymousImport a #

Foldable AnonymousImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousImport m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousImport a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousImport a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousImport a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousImport a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousImport a -> b #

foldr1 :: (a -> a -> a) -> AnonymousImport a -> a #

foldl1 :: (a -> a -> a) -> AnonymousImport a -> a #

toList :: AnonymousImport a -> [a] #

null :: AnonymousImport a -> Bool #

length :: AnonymousImport a -> Int #

elem :: Eq a => a -> AnonymousImport a -> Bool #

maximum :: Ord a => AnonymousImport a -> a #

minimum :: Ord a => AnonymousImport a -> a #

sum :: Num a => AnonymousImport a -> a #

product :: Num a => AnonymousImport a -> a #

Traversable AnonymousImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousImport a -> f (AnonymousImport b) #

sequenceA :: Applicative f => AnonymousImport (f a) -> f (AnonymousImport a) #

mapM :: Monad m => (a -> m b) -> AnonymousImport a -> m (AnonymousImport b) #

sequence :: Monad m => AnonymousImport (m a) -> m (AnonymousImport a) #

SymbolMatching AnonymousImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousImport a)

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 #

Generic1 AnonymousImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousImport :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousImport" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousImport Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousDot a Source #

Constructors

AnonymousDot 

Fields

Instances
Functor AnonymousDot Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousDot a -> AnonymousDot b #

(<$) :: a -> AnonymousDot b -> AnonymousDot a #

Foldable AnonymousDot Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousDot m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousDot a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousDot a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousDot a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousDot a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousDot a -> b #

foldr1 :: (a -> a -> a) -> AnonymousDot a -> a #

foldl1 :: (a -> a -> a) -> AnonymousDot a -> a #

toList :: AnonymousDot a -> [a] #

null :: AnonymousDot a -> Bool #

length :: AnonymousDot a -> Int #

elem :: Eq a => a -> AnonymousDot a -> Bool #

maximum :: Ord a => AnonymousDot a -> a #

minimum :: Ord a => AnonymousDot a -> a #

sum :: Num a => AnonymousDot a -> a #

product :: Num a => AnonymousDot a -> a #

Traversable AnonymousDot Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousDot a -> f (AnonymousDot b) #

sequenceA :: Applicative f => AnonymousDot (f a) -> f (AnonymousDot a) #

mapM :: Monad m => (a -> m b) -> AnonymousDot a -> m (AnonymousDot b) #

sequence :: Monad m => AnonymousDot (m a) -> m (AnonymousDot a) #

SymbolMatching AnonymousDot Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousDot Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousDot a)

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 #

Generic1 AnonymousDot Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousDot :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousDot" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousDot Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousFrom a Source #

Constructors

AnonymousFrom 

Fields

Instances
Functor AnonymousFrom Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousFrom a -> AnonymousFrom b #

(<$) :: a -> AnonymousFrom b -> AnonymousFrom a #

Foldable AnonymousFrom Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousFrom m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousFrom a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousFrom a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousFrom a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousFrom a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousFrom a -> b #

foldr1 :: (a -> a -> a) -> AnonymousFrom a -> a #

foldl1 :: (a -> a -> a) -> AnonymousFrom a -> a #

toList :: AnonymousFrom a -> [a] #

null :: AnonymousFrom a -> Bool #

length :: AnonymousFrom a -> Int #

elem :: Eq a => a -> AnonymousFrom a -> Bool #

maximum :: Ord a => AnonymousFrom a -> a #

minimum :: Ord a => AnonymousFrom a -> a #

sum :: Num a => AnonymousFrom a -> a #

product :: Num a => AnonymousFrom a -> a #

Traversable AnonymousFrom Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousFrom a -> f (AnonymousFrom b) #

sequenceA :: Applicative f => AnonymousFrom (f a) -> f (AnonymousFrom a) #

mapM :: Monad m => (a -> m b) -> AnonymousFrom a -> m (AnonymousFrom b) #

sequence :: Monad m => AnonymousFrom (m a) -> m (AnonymousFrom a) #

SymbolMatching AnonymousFrom Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousFrom Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousFrom a)

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 #

Generic1 AnonymousFrom Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousFrom :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousFrom" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousFrom Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousFuture a Source #

Constructors

AnonymousFuture 

Fields

Instances
Functor AnonymousFuture Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousFuture a -> AnonymousFuture b #

(<$) :: a -> AnonymousFuture b -> AnonymousFuture a #

Foldable AnonymousFuture Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousFuture m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousFuture a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousFuture a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousFuture a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousFuture a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousFuture a -> b #

foldr1 :: (a -> a -> a) -> AnonymousFuture a -> a #

foldl1 :: (a -> a -> a) -> AnonymousFuture a -> a #

toList :: AnonymousFuture a -> [a] #

null :: AnonymousFuture a -> Bool #

length :: AnonymousFuture a -> Int #

elem :: Eq a => a -> AnonymousFuture a -> Bool #

maximum :: Ord a => AnonymousFuture a -> a #

minimum :: Ord a => AnonymousFuture a -> a #

sum :: Num a => AnonymousFuture a -> a #

product :: Num a => AnonymousFuture a -> a #

Traversable AnonymousFuture Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousFuture a -> f (AnonymousFuture b) #

sequenceA :: Applicative f => AnonymousFuture (f a) -> f (AnonymousFuture a) #

mapM :: Monad m => (a -> m b) -> AnonymousFuture a -> m (AnonymousFuture b) #

sequence :: Monad m => AnonymousFuture (m a) -> m (AnonymousFuture a) #

SymbolMatching AnonymousFuture Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousFuture Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousFuture a)

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 #

Generic1 AnonymousFuture Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousFuture :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousFuture" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousFuture Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousLParen a Source #

Constructors

AnonymousLParen 

Fields

Instances
Functor AnonymousLParen Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousLParen a -> AnonymousLParen b #

(<$) :: a -> AnonymousLParen b -> AnonymousLParen a #

Foldable AnonymousLParen Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousLParen m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousLParen a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousLParen a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousLParen a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousLParen a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousLParen a -> b #

foldr1 :: (a -> a -> a) -> AnonymousLParen a -> a #

foldl1 :: (a -> a -> a) -> AnonymousLParen a -> a #

toList :: AnonymousLParen a -> [a] #

null :: AnonymousLParen a -> Bool #

length :: AnonymousLParen a -> Int #

elem :: Eq a => a -> AnonymousLParen a -> Bool #

maximum :: Ord a => AnonymousLParen a -> a #

minimum :: Ord a => AnonymousLParen a -> a #

sum :: Num a => AnonymousLParen a -> a #

product :: Num a => AnonymousLParen a -> a #

Traversable AnonymousLParen Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousLParen a -> f (AnonymousLParen b) #

sequenceA :: Applicative f => AnonymousLParen (f a) -> f (AnonymousLParen a) #

mapM :: Monad m => (a -> m b) -> AnonymousLParen a -> m (AnonymousLParen b) #

sequence :: Monad m => AnonymousLParen (m a) -> m (AnonymousLParen a) #

SymbolMatching AnonymousLParen Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousLParen Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousLParen a)

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 #

Generic1 AnonymousLParen Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousLParen :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousLParen" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousLParen Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousRParen a Source #

Constructors

AnonymousRParen 

Fields

Instances
Functor AnonymousRParen Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousRParen a -> AnonymousRParen b #

(<$) :: a -> AnonymousRParen b -> AnonymousRParen a #

Foldable AnonymousRParen Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousRParen m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousRParen a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousRParen a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousRParen a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousRParen a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousRParen a -> b #

foldr1 :: (a -> a -> a) -> AnonymousRParen a -> a #

foldl1 :: (a -> a -> a) -> AnonymousRParen a -> a #

toList :: AnonymousRParen a -> [a] #

null :: AnonymousRParen a -> Bool #

length :: AnonymousRParen a -> Int #

elem :: Eq a => a -> AnonymousRParen a -> Bool #

maximum :: Ord a => AnonymousRParen a -> a #

minimum :: Ord a => AnonymousRParen a -> a #

sum :: Num a => AnonymousRParen a -> a #

product :: Num a => AnonymousRParen a -> a #

Traversable AnonymousRParen Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousRParen a -> f (AnonymousRParen b) #

sequenceA :: Applicative f => AnonymousRParen (f a) -> f (AnonymousRParen a) #

mapM :: Monad m => (a -> m b) -> AnonymousRParen a -> m (AnonymousRParen b) #

sequence :: Monad m => AnonymousRParen (m a) -> m (AnonymousRParen a) #

SymbolMatching AnonymousRParen Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousRParen Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousRParen a)

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 #

Generic1 AnonymousRParen Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousRParen :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousRParen" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousRParen Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousComma a Source #

Constructors

AnonymousComma 

Fields

Instances
Functor AnonymousComma Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousComma a -> AnonymousComma b #

(<$) :: a -> AnonymousComma b -> AnonymousComma a #

Foldable AnonymousComma Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousComma m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousComma a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousComma a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousComma a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousComma a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousComma a -> b #

foldr1 :: (a -> a -> a) -> AnonymousComma a -> a #

foldl1 :: (a -> a -> a) -> AnonymousComma a -> a #

toList :: AnonymousComma a -> [a] #

null :: AnonymousComma a -> Bool #

length :: AnonymousComma a -> Int #

elem :: Eq a => a -> AnonymousComma a -> Bool #

maximum :: Ord a => AnonymousComma a -> a #

minimum :: Ord a => AnonymousComma a -> a #

sum :: Num a => AnonymousComma a -> a #

product :: Num a => AnonymousComma a -> a #

Traversable AnonymousComma Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousComma a -> f (AnonymousComma b) #

sequenceA :: Applicative f => AnonymousComma (f a) -> f (AnonymousComma a) #

mapM :: Monad m => (a -> m b) -> AnonymousComma a -> m (AnonymousComma b) #

sequence :: Monad m => AnonymousComma (m a) -> m (AnonymousComma a) #

SymbolMatching AnonymousComma Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousComma Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousComma a)

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 #

Generic1 AnonymousComma Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousComma :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousComma" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousComma Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousAs a Source #

Constructors

AnonymousAs 

Fields

Instances
Functor AnonymousAs Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousAs a -> AnonymousAs b #

(<$) :: a -> AnonymousAs b -> AnonymousAs a #

Foldable AnonymousAs Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousAs m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousAs a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousAs a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousAs a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousAs a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousAs a -> b #

foldr1 :: (a -> a -> a) -> AnonymousAs a -> a #

foldl1 :: (a -> a -> a) -> AnonymousAs a -> a #

toList :: AnonymousAs a -> [a] #

null :: AnonymousAs a -> Bool #

length :: AnonymousAs a -> Int #

elem :: Eq a => a -> AnonymousAs a -> Bool #

maximum :: Ord a => AnonymousAs a -> a #

minimum :: Ord a => AnonymousAs a -> a #

sum :: Num a => AnonymousAs a -> a #

product :: Num a => AnonymousAs a -> a #

Traversable AnonymousAs Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousAs a -> f (AnonymousAs b) #

sequenceA :: Applicative f => AnonymousAs (f a) -> f (AnonymousAs a) #

mapM :: Monad m => (a -> m b) -> AnonymousAs a -> m (AnonymousAs b) #

sequence :: Monad m => AnonymousAs (m a) -> m (AnonymousAs a) #

SymbolMatching AnonymousAs Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousAs Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousAs a)

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 #

Generic1 AnonymousAs Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousAs :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousAs" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousAs Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousStar a Source #

Constructors

AnonymousStar 

Fields

Instances
Functor AnonymousStar Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousStar a -> AnonymousStar b #

(<$) :: a -> AnonymousStar b -> AnonymousStar a #

Foldable AnonymousStar Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousStar m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousStar a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousStar a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousStar a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousStar a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousStar a -> b #

foldr1 :: (a -> a -> a) -> AnonymousStar a -> a #

foldl1 :: (a -> a -> a) -> AnonymousStar a -> a #

toList :: AnonymousStar a -> [a] #

null :: AnonymousStar a -> Bool #

length :: AnonymousStar a -> Int #

elem :: Eq a => a -> AnonymousStar a -> Bool #

maximum :: Ord a => AnonymousStar a -> a #

minimum :: Ord a => AnonymousStar a -> a #

sum :: Num a => AnonymousStar a -> a #

product :: Num a => AnonymousStar a -> a #

Traversable AnonymousStar Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousStar a -> f (AnonymousStar b) #

sequenceA :: Applicative f => AnonymousStar (f a) -> f (AnonymousStar a) #

mapM :: Monad m => (a -> m b) -> AnonymousStar a -> m (AnonymousStar b) #

sequence :: Monad m => AnonymousStar (m a) -> m (AnonymousStar a) #

SymbolMatching AnonymousStar Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousStar Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousStar a)

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 #

Generic1 AnonymousStar Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousStar :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousStar" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousStar Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousPrint a Source #

Constructors

AnonymousPrint 

Fields

Instances
Functor AnonymousPrint Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousPrint a -> AnonymousPrint b #

(<$) :: a -> AnonymousPrint b -> AnonymousPrint a #

Foldable AnonymousPrint Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousPrint m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousPrint a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousPrint a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousPrint a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousPrint a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousPrint a -> b #

foldr1 :: (a -> a -> a) -> AnonymousPrint a -> a #

foldl1 :: (a -> a -> a) -> AnonymousPrint a -> a #

toList :: AnonymousPrint a -> [a] #

null :: AnonymousPrint a -> Bool #

length :: AnonymousPrint a -> Int #

elem :: Eq a => a -> AnonymousPrint a -> Bool #

maximum :: Ord a => AnonymousPrint a -> a #

minimum :: Ord a => AnonymousPrint a -> a #

sum :: Num a => AnonymousPrint a -> a #

product :: Num a => AnonymousPrint a -> a #

Traversable AnonymousPrint Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousPrint a -> f (AnonymousPrint b) #

sequenceA :: Applicative f => AnonymousPrint (f a) -> f (AnonymousPrint a) #

mapM :: Monad m => (a -> m b) -> AnonymousPrint a -> m (AnonymousPrint b) #

sequence :: Monad m => AnonymousPrint (m a) -> m (AnonymousPrint a) #

SymbolMatching AnonymousPrint Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousPrint Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousPrint a)

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 #

Generic1 AnonymousPrint Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousPrint :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousPrint" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousPrint Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousRAngleRAngle a Source #

Constructors

AnonymousRAngleRAngle 

Fields

Instances
Functor AnonymousRAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousRAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousRAngleRAngle m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousRAngleRAngle a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousRAngleRAngle a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousRAngleRAngle a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousRAngleRAngle a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousRAngleRAngle a -> b #

foldr1 :: (a -> a -> a) -> AnonymousRAngleRAngle a -> a #

foldl1 :: (a -> a -> a) -> AnonymousRAngleRAngle a -> a #

toList :: AnonymousRAngleRAngle a -> [a] #

null :: AnonymousRAngleRAngle a -> Bool #

length :: AnonymousRAngleRAngle a -> Int #

elem :: Eq a => a -> AnonymousRAngleRAngle a -> Bool #

maximum :: Ord a => AnonymousRAngleRAngle a -> a #

minimum :: Ord a => AnonymousRAngleRAngle a -> a #

sum :: Num a => AnonymousRAngleRAngle a -> a #

product :: Num a => AnonymousRAngleRAngle a -> a #

Traversable AnonymousRAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousRAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousRAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousRAngleRAngle a)

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 #

Generic1 AnonymousRAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousRAngleRAngle :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousRAngleRAngle" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousRAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousAssert a Source #

Constructors

AnonymousAssert 

Fields

Instances
Functor AnonymousAssert Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousAssert a -> AnonymousAssert b #

(<$) :: a -> AnonymousAssert b -> AnonymousAssert a #

Foldable AnonymousAssert Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousAssert m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousAssert a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousAssert a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousAssert a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousAssert a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousAssert a -> b #

foldr1 :: (a -> a -> a) -> AnonymousAssert a -> a #

foldl1 :: (a -> a -> a) -> AnonymousAssert a -> a #

toList :: AnonymousAssert a -> [a] #

null :: AnonymousAssert a -> Bool #

length :: AnonymousAssert a -> Int #

elem :: Eq a => a -> AnonymousAssert a -> Bool #

maximum :: Ord a => AnonymousAssert a -> a #

minimum :: Ord a => AnonymousAssert a -> a #

sum :: Num a => AnonymousAssert a -> a #

product :: Num a => AnonymousAssert a -> a #

Traversable AnonymousAssert Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousAssert a -> f (AnonymousAssert b) #

sequenceA :: Applicative f => AnonymousAssert (f a) -> f (AnonymousAssert a) #

mapM :: Monad m => (a -> m b) -> AnonymousAssert a -> m (AnonymousAssert b) #

sequence :: Monad m => AnonymousAssert (m a) -> m (AnonymousAssert a) #

SymbolMatching AnonymousAssert Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousAssert Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousAssert a)

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 #

Generic1 AnonymousAssert Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousAssert :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousAssert" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousAssert Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousColonEqual a Source #

Constructors

AnonymousColonEqual 

Fields

Instances
Functor AnonymousColonEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousColonEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousColonEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousColonEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousColonEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousColonEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousColonEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousColonEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousColonEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousColonEqual a -> a #

toList :: AnonymousColonEqual a -> [a] #

null :: AnonymousColonEqual a -> Bool #

length :: AnonymousColonEqual a -> Int #

elem :: Eq a => a -> AnonymousColonEqual a -> Bool #

maximum :: Ord a => AnonymousColonEqual a -> a #

minimum :: Ord a => AnonymousColonEqual a -> a #

sum :: Num a => AnonymousColonEqual a -> a #

product :: Num a => AnonymousColonEqual a -> a #

Traversable AnonymousColonEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousColonEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousColonEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousColonEqual a)

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 #

Generic1 AnonymousColonEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousColonEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousColonEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousColonEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousReturn a Source #

Constructors

AnonymousReturn 

Fields

Instances
Functor AnonymousReturn Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousReturn a -> AnonymousReturn b #

(<$) :: a -> AnonymousReturn b -> AnonymousReturn a #

Foldable AnonymousReturn Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousReturn m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousReturn a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousReturn a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousReturn a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousReturn a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousReturn a -> b #

foldr1 :: (a -> a -> a) -> AnonymousReturn a -> a #

foldl1 :: (a -> a -> a) -> AnonymousReturn a -> a #

toList :: AnonymousReturn a -> [a] #

null :: AnonymousReturn a -> Bool #

length :: AnonymousReturn a -> Int #

elem :: Eq a => a -> AnonymousReturn a -> Bool #

maximum :: Ord a => AnonymousReturn a -> a #

minimum :: Ord a => AnonymousReturn a -> a #

sum :: Num a => AnonymousReturn a -> a #

product :: Num a => AnonymousReturn a -> a #

Traversable AnonymousReturn Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousReturn a -> f (AnonymousReturn b) #

sequenceA :: Applicative f => AnonymousReturn (f a) -> f (AnonymousReturn a) #

mapM :: Monad m => (a -> m b) -> AnonymousReturn a -> m (AnonymousReturn b) #

sequence :: Monad m => AnonymousReturn (m a) -> m (AnonymousReturn a) #

SymbolMatching AnonymousReturn Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousReturn Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousReturn a)

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 #

Generic1 AnonymousReturn Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousReturn :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousReturn" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousReturn Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousDel a Source #

Constructors

AnonymousDel 

Fields

Instances
Functor AnonymousDel Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousDel a -> AnonymousDel b #

(<$) :: a -> AnonymousDel b -> AnonymousDel a #

Foldable AnonymousDel Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousDel m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousDel a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousDel a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousDel a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousDel a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousDel a -> b #

foldr1 :: (a -> a -> a) -> AnonymousDel a -> a #

foldl1 :: (a -> a -> a) -> AnonymousDel a -> a #

toList :: AnonymousDel a -> [a] #

null :: AnonymousDel a -> Bool #

length :: AnonymousDel a -> Int #

elem :: Eq a => a -> AnonymousDel a -> Bool #

maximum :: Ord a => AnonymousDel a -> a #

minimum :: Ord a => AnonymousDel a -> a #

sum :: Num a => AnonymousDel a -> a #

product :: Num a => AnonymousDel a -> a #

Traversable AnonymousDel Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousDel a -> f (AnonymousDel b) #

sequenceA :: Applicative f => AnonymousDel (f a) -> f (AnonymousDel a) #

mapM :: Monad m => (a -> m b) -> AnonymousDel a -> m (AnonymousDel b) #

sequence :: Monad m => AnonymousDel (m a) -> m (AnonymousDel a) #

SymbolMatching AnonymousDel Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousDel Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousDel a)

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 #

Generic1 AnonymousDel Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousDel :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousDel" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousDel Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousRaise a Source #

Constructors

AnonymousRaise 

Fields

Instances
Functor AnonymousRaise Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousRaise a -> AnonymousRaise b #

(<$) :: a -> AnonymousRaise b -> AnonymousRaise a #

Foldable AnonymousRaise Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousRaise m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousRaise a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousRaise a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousRaise a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousRaise a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousRaise a -> b #

foldr1 :: (a -> a -> a) -> AnonymousRaise a -> a #

foldl1 :: (a -> a -> a) -> AnonymousRaise a -> a #

toList :: AnonymousRaise a -> [a] #

null :: AnonymousRaise a -> Bool #

length :: AnonymousRaise a -> Int #

elem :: Eq a => a -> AnonymousRaise a -> Bool #

maximum :: Ord a => AnonymousRaise a -> a #

minimum :: Ord a => AnonymousRaise a -> a #

sum :: Num a => AnonymousRaise a -> a #

product :: Num a => AnonymousRaise a -> a #

Traversable AnonymousRaise Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousRaise a -> f (AnonymousRaise b) #

sequenceA :: Applicative f => AnonymousRaise (f a) -> f (AnonymousRaise a) #

mapM :: Monad m => (a -> m b) -> AnonymousRaise a -> m (AnonymousRaise b) #

sequence :: Monad m => AnonymousRaise (m a) -> m (AnonymousRaise a) #

SymbolMatching AnonymousRaise Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousRaise Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousRaise a)

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 #

Generic1 AnonymousRaise Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousRaise :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousRaise" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousRaise Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousPass a Source #

Constructors

AnonymousPass 

Fields

Instances
Functor AnonymousPass Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousPass a -> AnonymousPass b #

(<$) :: a -> AnonymousPass b -> AnonymousPass a #

Foldable AnonymousPass Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousPass m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousPass a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousPass a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousPass a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousPass a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousPass a -> b #

foldr1 :: (a -> a -> a) -> AnonymousPass a -> a #

foldl1 :: (a -> a -> a) -> AnonymousPass a -> a #

toList :: AnonymousPass a -> [a] #

null :: AnonymousPass a -> Bool #

length :: AnonymousPass a -> Int #

elem :: Eq a => a -> AnonymousPass a -> Bool #

maximum :: Ord a => AnonymousPass a -> a #

minimum :: Ord a => AnonymousPass a -> a #

sum :: Num a => AnonymousPass a -> a #

product :: Num a => AnonymousPass a -> a #

Traversable AnonymousPass Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousPass a -> f (AnonymousPass b) #

sequenceA :: Applicative f => AnonymousPass (f a) -> f (AnonymousPass a) #

mapM :: Monad m => (a -> m b) -> AnonymousPass a -> m (AnonymousPass b) #

sequence :: Monad m => AnonymousPass (m a) -> m (AnonymousPass a) #

SymbolMatching AnonymousPass Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousPass Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousPass a)

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 #

Generic1 AnonymousPass Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousPass :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousPass" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousPass Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousBreak a Source #

Constructors

AnonymousBreak 

Fields

Instances
Functor AnonymousBreak Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousBreak a -> AnonymousBreak b #

(<$) :: a -> AnonymousBreak b -> AnonymousBreak a #

Foldable AnonymousBreak Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousBreak m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousBreak a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousBreak a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousBreak a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousBreak a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousBreak a -> b #

foldr1 :: (a -> a -> a) -> AnonymousBreak a -> a #

foldl1 :: (a -> a -> a) -> AnonymousBreak a -> a #

toList :: AnonymousBreak a -> [a] #

null :: AnonymousBreak a -> Bool #

length :: AnonymousBreak a -> Int #

elem :: Eq a => a -> AnonymousBreak a -> Bool #

maximum :: Ord a => AnonymousBreak a -> a #

minimum :: Ord a => AnonymousBreak a -> a #

sum :: Num a => AnonymousBreak a -> a #

product :: Num a => AnonymousBreak a -> a #

Traversable AnonymousBreak Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousBreak a -> f (AnonymousBreak b) #

sequenceA :: Applicative f => AnonymousBreak (f a) -> f (AnonymousBreak a) #

mapM :: Monad m => (a -> m b) -> AnonymousBreak a -> m (AnonymousBreak b) #

sequence :: Monad m => AnonymousBreak (m a) -> m (AnonymousBreak a) #

SymbolMatching AnonymousBreak Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousBreak Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousBreak a)

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 #

Generic1 AnonymousBreak Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousBreak :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousBreak" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousBreak Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousContinue a Source #

Constructors

AnonymousContinue 

Fields

Instances
Functor AnonymousContinue Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousContinue Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousContinue m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousContinue a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousContinue a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousContinue a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousContinue a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousContinue a -> b #

foldr1 :: (a -> a -> a) -> AnonymousContinue a -> a #

foldl1 :: (a -> a -> a) -> AnonymousContinue a -> a #

toList :: AnonymousContinue a -> [a] #

null :: AnonymousContinue a -> Bool #

length :: AnonymousContinue a -> Int #

elem :: Eq a => a -> AnonymousContinue a -> Bool #

maximum :: Ord a => AnonymousContinue a -> a #

minimum :: Ord a => AnonymousContinue a -> a #

sum :: Num a => AnonymousContinue a -> a #

product :: Num a => AnonymousContinue a -> a #

Traversable AnonymousContinue Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousContinue a -> f (AnonymousContinue b) #

sequenceA :: Applicative f => AnonymousContinue (f a) -> f (AnonymousContinue a) #

mapM :: Monad m => (a -> m b) -> AnonymousContinue a -> m (AnonymousContinue b) #

sequence :: Monad m => AnonymousContinue (m a) -> m (AnonymousContinue a) #

SymbolMatching AnonymousContinue Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousContinue Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousContinue a)

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 #

Generic1 AnonymousContinue Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousContinue :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousContinue" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousContinue Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousIf a Source #

Constructors

AnonymousIf 

Fields

Instances
Functor AnonymousIf Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousIf a -> AnonymousIf b #

(<$) :: a -> AnonymousIf b -> AnonymousIf a #

Foldable AnonymousIf Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousIf m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousIf a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousIf a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousIf a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousIf a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousIf a -> b #

foldr1 :: (a -> a -> a) -> AnonymousIf a -> a #

foldl1 :: (a -> a -> a) -> AnonymousIf a -> a #

toList :: AnonymousIf a -> [a] #

null :: AnonymousIf a -> Bool #

length :: AnonymousIf a -> Int #

elem :: Eq a => a -> AnonymousIf a -> Bool #

maximum :: Ord a => AnonymousIf a -> a #

minimum :: Ord a => AnonymousIf a -> a #

sum :: Num a => AnonymousIf a -> a #

product :: Num a => AnonymousIf a -> a #

Traversable AnonymousIf Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousIf a -> f (AnonymousIf b) #

sequenceA :: Applicative f => AnonymousIf (f a) -> f (AnonymousIf a) #

mapM :: Monad m => (a -> m b) -> AnonymousIf a -> m (AnonymousIf b) #

sequence :: Monad m => AnonymousIf (m a) -> m (AnonymousIf a) #

SymbolMatching AnonymousIf Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousIf Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousIf a)

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 #

Generic1 AnonymousIf Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousIf :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousIf" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousIf Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousColon a Source #

Constructors

AnonymousColon 

Fields

Instances
Functor AnonymousColon Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousColon a -> AnonymousColon b #

(<$) :: a -> AnonymousColon b -> AnonymousColon a #

Foldable AnonymousColon Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousColon m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousColon a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousColon a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousColon a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousColon a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousColon a -> b #

foldr1 :: (a -> a -> a) -> AnonymousColon a -> a #

foldl1 :: (a -> a -> a) -> AnonymousColon a -> a #

toList :: AnonymousColon a -> [a] #

null :: AnonymousColon a -> Bool #

length :: AnonymousColon a -> Int #

elem :: Eq a => a -> AnonymousColon a -> Bool #

maximum :: Ord a => AnonymousColon a -> a #

minimum :: Ord a => AnonymousColon a -> a #

sum :: Num a => AnonymousColon a -> a #

product :: Num a => AnonymousColon a -> a #

Traversable AnonymousColon Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousColon a -> f (AnonymousColon b) #

sequenceA :: Applicative f => AnonymousColon (f a) -> f (AnonymousColon a) #

mapM :: Monad m => (a -> m b) -> AnonymousColon a -> m (AnonymousColon b) #

sequence :: Monad m => AnonymousColon (m a) -> m (AnonymousColon a) #

SymbolMatching AnonymousColon Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousColon Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousColon a)

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 #

Generic1 AnonymousColon Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousColon :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousColon" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousColon Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousElif a Source #

Constructors

AnonymousElif 

Fields

Instances
Functor AnonymousElif Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousElif a -> AnonymousElif b #

(<$) :: a -> AnonymousElif b -> AnonymousElif a #

Foldable AnonymousElif Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousElif m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousElif a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousElif a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousElif a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousElif a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousElif a -> b #

foldr1 :: (a -> a -> a) -> AnonymousElif a -> a #

foldl1 :: (a -> a -> a) -> AnonymousElif a -> a #

toList :: AnonymousElif a -> [a] #

null :: AnonymousElif a -> Bool #

length :: AnonymousElif a -> Int #

elem :: Eq a => a -> AnonymousElif a -> Bool #

maximum :: Ord a => AnonymousElif a -> a #

minimum :: Ord a => AnonymousElif a -> a #

sum :: Num a => AnonymousElif a -> a #

product :: Num a => AnonymousElif a -> a #

Traversable AnonymousElif Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousElif a -> f (AnonymousElif b) #

sequenceA :: Applicative f => AnonymousElif (f a) -> f (AnonymousElif a) #

mapM :: Monad m => (a -> m b) -> AnonymousElif a -> m (AnonymousElif b) #

sequence :: Monad m => AnonymousElif (m a) -> m (AnonymousElif a) #

SymbolMatching AnonymousElif Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousElif Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousElif a)

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 #

Generic1 AnonymousElif Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousElif :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousElif" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousElif Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousElse a Source #

Constructors

AnonymousElse 

Fields

Instances
Functor AnonymousElse Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousElse a -> AnonymousElse b #

(<$) :: a -> AnonymousElse b -> AnonymousElse a #

Foldable AnonymousElse Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousElse m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousElse a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousElse a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousElse a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousElse a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousElse a -> b #

foldr1 :: (a -> a -> a) -> AnonymousElse a -> a #

foldl1 :: (a -> a -> a) -> AnonymousElse a -> a #

toList :: AnonymousElse a -> [a] #

null :: AnonymousElse a -> Bool #

length :: AnonymousElse a -> Int #

elem :: Eq a => a -> AnonymousElse a -> Bool #

maximum :: Ord a => AnonymousElse a -> a #

minimum :: Ord a => AnonymousElse a -> a #

sum :: Num a => AnonymousElse a -> a #

product :: Num a => AnonymousElse a -> a #

Traversable AnonymousElse Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousElse a -> f (AnonymousElse b) #

sequenceA :: Applicative f => AnonymousElse (f a) -> f (AnonymousElse a) #

mapM :: Monad m => (a -> m b) -> AnonymousElse a -> m (AnonymousElse b) #

sequence :: Monad m => AnonymousElse (m a) -> m (AnonymousElse a) #

SymbolMatching AnonymousElse Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousElse Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousElse a)

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 #

Generic1 AnonymousElse Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousElse :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousElse" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousElse Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousAsync a Source #

Constructors

AnonymousAsync 

Fields

Instances
Functor AnonymousAsync Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousAsync a -> AnonymousAsync b #

(<$) :: a -> AnonymousAsync b -> AnonymousAsync a #

Foldable AnonymousAsync Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousAsync m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousAsync a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousAsync a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousAsync a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousAsync a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousAsync a -> b #

foldr1 :: (a -> a -> a) -> AnonymousAsync a -> a #

foldl1 :: (a -> a -> a) -> AnonymousAsync a -> a #

toList :: AnonymousAsync a -> [a] #

null :: AnonymousAsync a -> Bool #

length :: AnonymousAsync a -> Int #

elem :: Eq a => a -> AnonymousAsync a -> Bool #

maximum :: Ord a => AnonymousAsync a -> a #

minimum :: Ord a => AnonymousAsync a -> a #

sum :: Num a => AnonymousAsync a -> a #

product :: Num a => AnonymousAsync a -> a #

Traversable AnonymousAsync Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousAsync a -> f (AnonymousAsync b) #

sequenceA :: Applicative f => AnonymousAsync (f a) -> f (AnonymousAsync a) #

mapM :: Monad m => (a -> m b) -> AnonymousAsync a -> m (AnonymousAsync b) #

sequence :: Monad m => AnonymousAsync (m a) -> m (AnonymousAsync a) #

SymbolMatching AnonymousAsync Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousAsync Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousAsync a)

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 #

Generic1 AnonymousAsync Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousAsync :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousAsync" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousAsync Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousFor a Source #

Constructors

AnonymousFor 

Fields

Instances
Functor AnonymousFor Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousFor a -> AnonymousFor b #

(<$) :: a -> AnonymousFor b -> AnonymousFor a #

Foldable AnonymousFor Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousFor m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousFor a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousFor a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousFor a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousFor a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousFor a -> b #

foldr1 :: (a -> a -> a) -> AnonymousFor a -> a #

foldl1 :: (a -> a -> a) -> AnonymousFor a -> a #

toList :: AnonymousFor a -> [a] #

null :: AnonymousFor a -> Bool #

length :: AnonymousFor a -> Int #

elem :: Eq a => a -> AnonymousFor a -> Bool #

maximum :: Ord a => AnonymousFor a -> a #

minimum :: Ord a => AnonymousFor a -> a #

sum :: Num a => AnonymousFor a -> a #

product :: Num a => AnonymousFor a -> a #

Traversable AnonymousFor Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousFor a -> f (AnonymousFor b) #

sequenceA :: Applicative f => AnonymousFor (f a) -> f (AnonymousFor a) #

mapM :: Monad m => (a -> m b) -> AnonymousFor a -> m (AnonymousFor b) #

sequence :: Monad m => AnonymousFor (m a) -> m (AnonymousFor a) #

SymbolMatching AnonymousFor Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousFor Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousFor a)

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 #

Generic1 AnonymousFor Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousFor :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousFor" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousFor Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousIn a Source #

Constructors

AnonymousIn 

Fields

Instances
Functor AnonymousIn Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousIn a -> AnonymousIn b #

(<$) :: a -> AnonymousIn b -> AnonymousIn a #

Foldable AnonymousIn Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousIn m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousIn a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousIn a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousIn a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousIn a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousIn a -> b #

foldr1 :: (a -> a -> a) -> AnonymousIn a -> a #

foldl1 :: (a -> a -> a) -> AnonymousIn a -> a #

toList :: AnonymousIn a -> [a] #

null :: AnonymousIn a -> Bool #

length :: AnonymousIn a -> Int #

elem :: Eq a => a -> AnonymousIn a -> Bool #

maximum :: Ord a => AnonymousIn a -> a #

minimum :: Ord a => AnonymousIn a -> a #

sum :: Num a => AnonymousIn a -> a #

product :: Num a => AnonymousIn a -> a #

Traversable AnonymousIn Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousIn a -> f (AnonymousIn b) #

sequenceA :: Applicative f => AnonymousIn (f a) -> f (AnonymousIn a) #

mapM :: Monad m => (a -> m b) -> AnonymousIn a -> m (AnonymousIn b) #

sequence :: Monad m => AnonymousIn (m a) -> m (AnonymousIn a) #

SymbolMatching AnonymousIn Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousIn Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousIn a)

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 #

Generic1 AnonymousIn Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousIn :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousIn" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousIn Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousWhile a Source #

Constructors

AnonymousWhile 

Fields

Instances
Functor AnonymousWhile Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousWhile a -> AnonymousWhile b #

(<$) :: a -> AnonymousWhile b -> AnonymousWhile a #

Foldable AnonymousWhile Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousWhile m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousWhile a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousWhile a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousWhile a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousWhile a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousWhile a -> b #

foldr1 :: (a -> a -> a) -> AnonymousWhile a -> a #

foldl1 :: (a -> a -> a) -> AnonymousWhile a -> a #

toList :: AnonymousWhile a -> [a] #

null :: AnonymousWhile a -> Bool #

length :: AnonymousWhile a -> Int #

elem :: Eq a => a -> AnonymousWhile a -> Bool #

maximum :: Ord a => AnonymousWhile a -> a #

minimum :: Ord a => AnonymousWhile a -> a #

sum :: Num a => AnonymousWhile a -> a #

product :: Num a => AnonymousWhile a -> a #

Traversable AnonymousWhile Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousWhile a -> f (AnonymousWhile b) #

sequenceA :: Applicative f => AnonymousWhile (f a) -> f (AnonymousWhile a) #

mapM :: Monad m => (a -> m b) -> AnonymousWhile a -> m (AnonymousWhile b) #

sequence :: Monad m => AnonymousWhile (m a) -> m (AnonymousWhile a) #

SymbolMatching AnonymousWhile Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousWhile Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousWhile a)

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 #

Generic1 AnonymousWhile Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousWhile :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousWhile" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousWhile Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousTry a Source #

Constructors

AnonymousTry 

Fields

Instances
Functor AnonymousTry Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousTry a -> AnonymousTry b #

(<$) :: a -> AnonymousTry b -> AnonymousTry a #

Foldable AnonymousTry Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousTry m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousTry a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousTry a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousTry a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousTry a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousTry a -> b #

foldr1 :: (a -> a -> a) -> AnonymousTry a -> a #

foldl1 :: (a -> a -> a) -> AnonymousTry a -> a #

toList :: AnonymousTry a -> [a] #

null :: AnonymousTry a -> Bool #

length :: AnonymousTry a -> Int #

elem :: Eq a => a -> AnonymousTry a -> Bool #

maximum :: Ord a => AnonymousTry a -> a #

minimum :: Ord a => AnonymousTry a -> a #

sum :: Num a => AnonymousTry a -> a #

product :: Num a => AnonymousTry a -> a #

Traversable AnonymousTry Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousTry a -> f (AnonymousTry b) #

sequenceA :: Applicative f => AnonymousTry (f a) -> f (AnonymousTry a) #

mapM :: Monad m => (a -> m b) -> AnonymousTry a -> m (AnonymousTry b) #

sequence :: Monad m => AnonymousTry (m a) -> m (AnonymousTry a) #

SymbolMatching AnonymousTry Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousTry Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousTry a)

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 #

Generic1 AnonymousTry Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousTry :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousTry" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousTry Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousExcept a Source #

Constructors

AnonymousExcept 

Fields

Instances
Functor AnonymousExcept Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousExcept a -> AnonymousExcept b #

(<$) :: a -> AnonymousExcept b -> AnonymousExcept a #

Foldable AnonymousExcept Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousExcept m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousExcept a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousExcept a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousExcept a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousExcept a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousExcept a -> b #

foldr1 :: (a -> a -> a) -> AnonymousExcept a -> a #

foldl1 :: (a -> a -> a) -> AnonymousExcept a -> a #

toList :: AnonymousExcept a -> [a] #

null :: AnonymousExcept a -> Bool #

length :: AnonymousExcept a -> Int #

elem :: Eq a => a -> AnonymousExcept a -> Bool #

maximum :: Ord a => AnonymousExcept a -> a #

minimum :: Ord a => AnonymousExcept a -> a #

sum :: Num a => AnonymousExcept a -> a #

product :: Num a => AnonymousExcept a -> a #

Traversable AnonymousExcept Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousExcept a -> f (AnonymousExcept b) #

sequenceA :: Applicative f => AnonymousExcept (f a) -> f (AnonymousExcept a) #

mapM :: Monad m => (a -> m b) -> AnonymousExcept a -> m (AnonymousExcept b) #

sequence :: Monad m => AnonymousExcept (m a) -> m (AnonymousExcept a) #

SymbolMatching AnonymousExcept Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousExcept Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousExcept a)

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 #

Generic1 AnonymousExcept Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousExcept :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousExcept" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousExcept Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousFinally a Source #

Constructors

AnonymousFinally 

Fields

Instances
Functor AnonymousFinally Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousFinally a -> AnonymousFinally b #

(<$) :: a -> AnonymousFinally b -> AnonymousFinally a #

Foldable AnonymousFinally Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousFinally m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousFinally a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousFinally a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousFinally a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousFinally a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousFinally a -> b #

foldr1 :: (a -> a -> a) -> AnonymousFinally a -> a #

foldl1 :: (a -> a -> a) -> AnonymousFinally a -> a #

toList :: AnonymousFinally a -> [a] #

null :: AnonymousFinally a -> Bool #

length :: AnonymousFinally a -> Int #

elem :: Eq a => a -> AnonymousFinally a -> Bool #

maximum :: Ord a => AnonymousFinally a -> a #

minimum :: Ord a => AnonymousFinally a -> a #

sum :: Num a => AnonymousFinally a -> a #

product :: Num a => AnonymousFinally a -> a #

Traversable AnonymousFinally Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousFinally a -> f (AnonymousFinally b) #

sequenceA :: Applicative f => AnonymousFinally (f a) -> f (AnonymousFinally a) #

mapM :: Monad m => (a -> m b) -> AnonymousFinally a -> m (AnonymousFinally b) #

sequence :: Monad m => AnonymousFinally (m a) -> m (AnonymousFinally a) #

SymbolMatching AnonymousFinally Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousFinally Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousFinally a)

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 #

Generic1 AnonymousFinally Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousFinally :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousFinally" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousFinally Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousWith a Source #

Constructors

AnonymousWith 

Fields

Instances
Functor AnonymousWith Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousWith a -> AnonymousWith b #

(<$) :: a -> AnonymousWith b -> AnonymousWith a #

Foldable AnonymousWith Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousWith m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousWith a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousWith a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousWith a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousWith a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousWith a -> b #

foldr1 :: (a -> a -> a) -> AnonymousWith a -> a #

foldl1 :: (a -> a -> a) -> AnonymousWith a -> a #

toList :: AnonymousWith a -> [a] #

null :: AnonymousWith a -> Bool #

length :: AnonymousWith a -> Int #

elem :: Eq a => a -> AnonymousWith a -> Bool #

maximum :: Ord a => AnonymousWith a -> a #

minimum :: Ord a => AnonymousWith a -> a #

sum :: Num a => AnonymousWith a -> a #

product :: Num a => AnonymousWith a -> a #

Traversable AnonymousWith Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousWith a -> f (AnonymousWith b) #

sequenceA :: Applicative f => AnonymousWith (f a) -> f (AnonymousWith a) #

mapM :: Monad m => (a -> m b) -> AnonymousWith a -> m (AnonymousWith b) #

sequence :: Monad m => AnonymousWith (m a) -> m (AnonymousWith a) #

SymbolMatching AnonymousWith Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousWith Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousWith a)

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 #

Generic1 AnonymousWith Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousWith :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousWith" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousWith Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousDef a Source #

Constructors

AnonymousDef 

Fields

Instances
Functor AnonymousDef Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousDef a -> AnonymousDef b #

(<$) :: a -> AnonymousDef b -> AnonymousDef a #

Foldable AnonymousDef Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousDef m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousDef a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousDef a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousDef a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousDef a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousDef a -> b #

foldr1 :: (a -> a -> a) -> AnonymousDef a -> a #

foldl1 :: (a -> a -> a) -> AnonymousDef a -> a #

toList :: AnonymousDef a -> [a] #

null :: AnonymousDef a -> Bool #

length :: AnonymousDef a -> Int #

elem :: Eq a => a -> AnonymousDef a -> Bool #

maximum :: Ord a => AnonymousDef a -> a #

minimum :: Ord a => AnonymousDef a -> a #

sum :: Num a => AnonymousDef a -> a #

product :: Num a => AnonymousDef a -> a #

Traversable AnonymousDef Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousDef a -> f (AnonymousDef b) #

sequenceA :: Applicative f => AnonymousDef (f a) -> f (AnonymousDef a) #

mapM :: Monad m => (a -> m b) -> AnonymousDef a -> m (AnonymousDef b) #

sequence :: Monad m => AnonymousDef (m a) -> m (AnonymousDef a) #

SymbolMatching AnonymousDef Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousDef Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousDef a)

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 #

Generic1 AnonymousDef Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousDef :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousDef" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousDef Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousMinusRAngle a Source #

Constructors

AnonymousMinusRAngle 

Fields

Instances
Functor AnonymousMinusRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousMinusRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousMinusRAngle m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousMinusRAngle a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousMinusRAngle a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousMinusRAngle a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousMinusRAngle a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousMinusRAngle a -> b #

foldr1 :: (a -> a -> a) -> AnonymousMinusRAngle a -> a #

foldl1 :: (a -> a -> a) -> AnonymousMinusRAngle a -> a #

toList :: AnonymousMinusRAngle a -> [a] #

null :: AnonymousMinusRAngle a -> Bool #

length :: AnonymousMinusRAngle a -> Int #

elem :: Eq a => a -> AnonymousMinusRAngle a -> Bool #

maximum :: Ord a => AnonymousMinusRAngle a -> a #

minimum :: Ord a => AnonymousMinusRAngle a -> a #

sum :: Num a => AnonymousMinusRAngle a -> a #

product :: Num a => AnonymousMinusRAngle a -> a #

Traversable AnonymousMinusRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousMinusRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousMinusRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousMinusRAngle a)

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 #

Generic1 AnonymousMinusRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousMinusRAngle :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousMinusRAngle" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousMinusRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousEqual a Source #

Constructors

AnonymousEqual 

Fields

Instances
Functor AnonymousEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousEqual a -> AnonymousEqual b #

(<$) :: a -> AnonymousEqual b -> AnonymousEqual a #

Foldable AnonymousEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousEqual a -> a #

toList :: AnonymousEqual a -> [a] #

null :: AnonymousEqual a -> Bool #

length :: AnonymousEqual a -> Int #

elem :: Eq a => a -> AnonymousEqual a -> Bool #

maximum :: Ord a => AnonymousEqual a -> a #

minimum :: Ord a => AnonymousEqual a -> a #

sum :: Num a => AnonymousEqual a -> a #

product :: Num a => AnonymousEqual a -> a #

Traversable AnonymousEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousEqual a -> f (AnonymousEqual b) #

sequenceA :: Applicative f => AnonymousEqual (f a) -> f (AnonymousEqual a) #

mapM :: Monad m => (a -> m b) -> AnonymousEqual a -> m (AnonymousEqual b) #

sequence :: Monad m => AnonymousEqual (m a) -> m (AnonymousEqual a) #

SymbolMatching AnonymousEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousEqual a)

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 #

Generic1 AnonymousEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousGlobal a Source #

Constructors

AnonymousGlobal 

Fields

Instances
Functor AnonymousGlobal Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousGlobal a -> AnonymousGlobal b #

(<$) :: a -> AnonymousGlobal b -> AnonymousGlobal a #

Foldable AnonymousGlobal Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousGlobal m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousGlobal a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousGlobal a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousGlobal a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousGlobal a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousGlobal a -> b #

foldr1 :: (a -> a -> a) -> AnonymousGlobal a -> a #

foldl1 :: (a -> a -> a) -> AnonymousGlobal a -> a #

toList :: AnonymousGlobal a -> [a] #

null :: AnonymousGlobal a -> Bool #

length :: AnonymousGlobal a -> Int #

elem :: Eq a => a -> AnonymousGlobal a -> Bool #

maximum :: Ord a => AnonymousGlobal a -> a #

minimum :: Ord a => AnonymousGlobal a -> a #

sum :: Num a => AnonymousGlobal a -> a #

product :: Num a => AnonymousGlobal a -> a #

Traversable AnonymousGlobal Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousGlobal a -> f (AnonymousGlobal b) #

sequenceA :: Applicative f => AnonymousGlobal (f a) -> f (AnonymousGlobal a) #

mapM :: Monad m => (a -> m b) -> AnonymousGlobal a -> m (AnonymousGlobal b) #

sequence :: Monad m => AnonymousGlobal (m a) -> m (AnonymousGlobal a) #

SymbolMatching AnonymousGlobal Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousGlobal Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousGlobal a)

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 #

Generic1 AnonymousGlobal Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousGlobal :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousGlobal" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousGlobal Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousNonlocal a Source #

Constructors

AnonymousNonlocal 

Fields

Instances
Functor AnonymousNonlocal Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousNonlocal Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousNonlocal m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousNonlocal a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousNonlocal a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousNonlocal a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousNonlocal a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousNonlocal a -> b #

foldr1 :: (a -> a -> a) -> AnonymousNonlocal a -> a #

foldl1 :: (a -> a -> a) -> AnonymousNonlocal a -> a #

toList :: AnonymousNonlocal a -> [a] #

null :: AnonymousNonlocal a -> Bool #

length :: AnonymousNonlocal a -> Int #

elem :: Eq a => a -> AnonymousNonlocal a -> Bool #

maximum :: Ord a => AnonymousNonlocal a -> a #

minimum :: Ord a => AnonymousNonlocal a -> a #

sum :: Num a => AnonymousNonlocal a -> a #

product :: Num a => AnonymousNonlocal a -> a #

Traversable AnonymousNonlocal Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousNonlocal a -> f (AnonymousNonlocal b) #

sequenceA :: Applicative f => AnonymousNonlocal (f a) -> f (AnonymousNonlocal a) #

mapM :: Monad m => (a -> m b) -> AnonymousNonlocal a -> m (AnonymousNonlocal b) #

sequence :: Monad m => AnonymousNonlocal (m a) -> m (AnonymousNonlocal a) #

SymbolMatching AnonymousNonlocal Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousNonlocal Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousNonlocal a)

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 #

Generic1 AnonymousNonlocal Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousNonlocal :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousNonlocal" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousNonlocal Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousExec a Source #

Constructors

AnonymousExec 

Fields

Instances
Functor AnonymousExec Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousExec a -> AnonymousExec b #

(<$) :: a -> AnonymousExec b -> AnonymousExec a #

Foldable AnonymousExec Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousExec m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousExec a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousExec a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousExec a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousExec a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousExec a -> b #

foldr1 :: (a -> a -> a) -> AnonymousExec a -> a #

foldl1 :: (a -> a -> a) -> AnonymousExec a -> a #

toList :: AnonymousExec a -> [a] #

null :: AnonymousExec a -> Bool #

length :: AnonymousExec a -> Int #

elem :: Eq a => a -> AnonymousExec a -> Bool #

maximum :: Ord a => AnonymousExec a -> a #

minimum :: Ord a => AnonymousExec a -> a #

sum :: Num a => AnonymousExec a -> a #

product :: Num a => AnonymousExec a -> a #

Traversable AnonymousExec Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousExec a -> f (AnonymousExec b) #

sequenceA :: Applicative f => AnonymousExec (f a) -> f (AnonymousExec a) #

mapM :: Monad m => (a -> m b) -> AnonymousExec a -> m (AnonymousExec b) #

sequence :: Monad m => AnonymousExec (m a) -> m (AnonymousExec a) #

SymbolMatching AnonymousExec Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousExec Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousExec a)

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 #

Generic1 AnonymousExec Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousExec :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousExec" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousExec Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousClass a Source #

Constructors

AnonymousClass 

Fields

Instances
Functor AnonymousClass Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousClass a -> AnonymousClass b #

(<$) :: a -> AnonymousClass b -> AnonymousClass a #

Foldable AnonymousClass Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousClass m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousClass a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousClass a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousClass a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousClass a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousClass a -> b #

foldr1 :: (a -> a -> a) -> AnonymousClass a -> a #

foldl1 :: (a -> a -> a) -> AnonymousClass a -> a #

toList :: AnonymousClass a -> [a] #

null :: AnonymousClass a -> Bool #

length :: AnonymousClass a -> Int #

elem :: Eq a => a -> AnonymousClass a -> Bool #

maximum :: Ord a => AnonymousClass a -> a #

minimum :: Ord a => AnonymousClass a -> a #

sum :: Num a => AnonymousClass a -> a #

product :: Num a => AnonymousClass a -> a #

Traversable AnonymousClass Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousClass a -> f (AnonymousClass b) #

sequenceA :: Applicative f => AnonymousClass (f a) -> f (AnonymousClass a) #

mapM :: Monad m => (a -> m b) -> AnonymousClass a -> m (AnonymousClass b) #

sequence :: Monad m => AnonymousClass (m a) -> m (AnonymousClass a) #

SymbolMatching AnonymousClass Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousClass Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousClass a)

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 #

Generic1 AnonymousClass Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousClass :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousClass" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousClass Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousAt a Source #

Constructors

AnonymousAt 

Fields

Instances
Functor AnonymousAt Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousAt a -> AnonymousAt b #

(<$) :: a -> AnonymousAt b -> AnonymousAt a #

Foldable AnonymousAt Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousAt m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousAt a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousAt a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousAt a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousAt a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousAt a -> b #

foldr1 :: (a -> a -> a) -> AnonymousAt a -> a #

foldl1 :: (a -> a -> a) -> AnonymousAt a -> a #

toList :: AnonymousAt a -> [a] #

null :: AnonymousAt a -> Bool #

length :: AnonymousAt a -> Int #

elem :: Eq a => a -> AnonymousAt a -> Bool #

maximum :: Ord a => AnonymousAt a -> a #

minimum :: Ord a => AnonymousAt a -> a #

sum :: Num a => AnonymousAt a -> a #

product :: Num a => AnonymousAt a -> a #

Traversable AnonymousAt Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousAt a -> f (AnonymousAt b) #

sequenceA :: Applicative f => AnonymousAt (f a) -> f (AnonymousAt a) #

mapM :: Monad m => (a -> m b) -> AnonymousAt a -> m (AnonymousAt b) #

sequence :: Monad m => AnonymousAt (m a) -> m (AnonymousAt a) #

SymbolMatching AnonymousAt Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousAt Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousAt a)

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 #

Generic1 AnonymousAt Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousAt :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousAt" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousAt Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousNot a Source #

Constructors

AnonymousNot 

Fields

Instances
Functor AnonymousNot Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousNot a -> AnonymousNot b #

(<$) :: a -> AnonymousNot b -> AnonymousNot a #

Foldable AnonymousNot Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousNot m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousNot a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousNot a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousNot a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousNot a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousNot a -> b #

foldr1 :: (a -> a -> a) -> AnonymousNot a -> a #

foldl1 :: (a -> a -> a) -> AnonymousNot a -> a #

toList :: AnonymousNot a -> [a] #

null :: AnonymousNot a -> Bool #

length :: AnonymousNot a -> Int #

elem :: Eq a => a -> AnonymousNot a -> Bool #

maximum :: Ord a => AnonymousNot a -> a #

minimum :: Ord a => AnonymousNot a -> a #

sum :: Num a => AnonymousNot a -> a #

product :: Num a => AnonymousNot a -> a #

Traversable AnonymousNot Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousNot a -> f (AnonymousNot b) #

sequenceA :: Applicative f => AnonymousNot (f a) -> f (AnonymousNot a) #

mapM :: Monad m => (a -> m b) -> AnonymousNot a -> m (AnonymousNot b) #

sequence :: Monad m => AnonymousNot (m a) -> m (AnonymousNot a) #

SymbolMatching AnonymousNot Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousNot Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousNot a)

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 #

Generic1 AnonymousNot Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousNot :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousNot" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousNot Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousAnd a Source #

Constructors

AnonymousAnd 

Fields

Instances
Functor AnonymousAnd Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousAnd a -> AnonymousAnd b #

(<$) :: a -> AnonymousAnd b -> AnonymousAnd a #

Foldable AnonymousAnd Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousAnd m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousAnd a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousAnd a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousAnd a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousAnd a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousAnd a -> b #

foldr1 :: (a -> a -> a) -> AnonymousAnd a -> a #

foldl1 :: (a -> a -> a) -> AnonymousAnd a -> a #

toList :: AnonymousAnd a -> [a] #

null :: AnonymousAnd a -> Bool #

length :: AnonymousAnd a -> Int #

elem :: Eq a => a -> AnonymousAnd a -> Bool #

maximum :: Ord a => AnonymousAnd a -> a #

minimum :: Ord a => AnonymousAnd a -> a #

sum :: Num a => AnonymousAnd a -> a #

product :: Num a => AnonymousAnd a -> a #

Traversable AnonymousAnd Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousAnd a -> f (AnonymousAnd b) #

sequenceA :: Applicative f => AnonymousAnd (f a) -> f (AnonymousAnd a) #

mapM :: Monad m => (a -> m b) -> AnonymousAnd a -> m (AnonymousAnd b) #

sequence :: Monad m => AnonymousAnd (m a) -> m (AnonymousAnd a) #

SymbolMatching AnonymousAnd Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousAnd Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousAnd a)

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 #

Generic1 AnonymousAnd Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousAnd :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousAnd" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousAnd Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousOr a Source #

Constructors

AnonymousOr 

Fields

Instances
Functor AnonymousOr Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousOr a -> AnonymousOr b #

(<$) :: a -> AnonymousOr b -> AnonymousOr a #

Foldable AnonymousOr Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousOr m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousOr a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousOr a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousOr a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousOr a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousOr a -> b #

foldr1 :: (a -> a -> a) -> AnonymousOr a -> a #

foldl1 :: (a -> a -> a) -> AnonymousOr a -> a #

toList :: AnonymousOr a -> [a] #

null :: AnonymousOr a -> Bool #

length :: AnonymousOr a -> Int #

elem :: Eq a => a -> AnonymousOr a -> Bool #

maximum :: Ord a => AnonymousOr a -> a #

minimum :: Ord a => AnonymousOr a -> a #

sum :: Num a => AnonymousOr a -> a #

product :: Num a => AnonymousOr a -> a #

Traversable AnonymousOr Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousOr a -> f (AnonymousOr b) #

sequenceA :: Applicative f => AnonymousOr (f a) -> f (AnonymousOr a) #

mapM :: Monad m => (a -> m b) -> AnonymousOr a -> m (AnonymousOr b) #

sequence :: Monad m => AnonymousOr (m a) -> m (AnonymousOr a) #

SymbolMatching AnonymousOr Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousOr Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousOr a)

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 #

Generic1 AnonymousOr Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousOr :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousOr" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousOr Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousPlus a Source #

Constructors

AnonymousPlus 

Fields

Instances
Functor AnonymousPlus Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousPlus a -> AnonymousPlus b #

(<$) :: a -> AnonymousPlus b -> AnonymousPlus a #

Foldable AnonymousPlus Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousPlus m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousPlus a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousPlus a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousPlus a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousPlus a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousPlus a -> b #

foldr1 :: (a -> a -> a) -> AnonymousPlus a -> a #

foldl1 :: (a -> a -> a) -> AnonymousPlus a -> a #

toList :: AnonymousPlus a -> [a] #

null :: AnonymousPlus a -> Bool #

length :: AnonymousPlus a -> Int #

elem :: Eq a => a -> AnonymousPlus a -> Bool #

maximum :: Ord a => AnonymousPlus a -> a #

minimum :: Ord a => AnonymousPlus a -> a #

sum :: Num a => AnonymousPlus a -> a #

product :: Num a => AnonymousPlus a -> a #

Traversable AnonymousPlus Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousPlus a -> f (AnonymousPlus b) #

sequenceA :: Applicative f => AnonymousPlus (f a) -> f (AnonymousPlus a) #

mapM :: Monad m => (a -> m b) -> AnonymousPlus a -> m (AnonymousPlus b) #

sequence :: Monad m => AnonymousPlus (m a) -> m (AnonymousPlus a) #

SymbolMatching AnonymousPlus Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousPlus Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousPlus a)

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 #

Generic1 AnonymousPlus Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousPlus :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousPlus" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousPlus Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousMinus a Source #

Constructors

AnonymousMinus 

Fields

Instances
Functor AnonymousMinus Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousMinus a -> AnonymousMinus b #

(<$) :: a -> AnonymousMinus b -> AnonymousMinus a #

Foldable AnonymousMinus Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousMinus m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousMinus a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousMinus a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousMinus a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousMinus a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousMinus a -> b #

foldr1 :: (a -> a -> a) -> AnonymousMinus a -> a #

foldl1 :: (a -> a -> a) -> AnonymousMinus a -> a #

toList :: AnonymousMinus a -> [a] #

null :: AnonymousMinus a -> Bool #

length :: AnonymousMinus a -> Int #

elem :: Eq a => a -> AnonymousMinus a -> Bool #

maximum :: Ord a => AnonymousMinus a -> a #

minimum :: Ord a => AnonymousMinus a -> a #

sum :: Num a => AnonymousMinus a -> a #

product :: Num a => AnonymousMinus a -> a #

Traversable AnonymousMinus Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousMinus a -> f (AnonymousMinus b) #

sequenceA :: Applicative f => AnonymousMinus (f a) -> f (AnonymousMinus a) #

mapM :: Monad m => (a -> m b) -> AnonymousMinus a -> m (AnonymousMinus b) #

sequence :: Monad m => AnonymousMinus (m a) -> m (AnonymousMinus a) #

SymbolMatching AnonymousMinus Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousMinus Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousMinus a)

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 #

Generic1 AnonymousMinus Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousMinus :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousMinus" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousMinus Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousSlash a Source #

Constructors

AnonymousSlash 

Fields

Instances
Functor AnonymousSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousSlash a -> AnonymousSlash b #

(<$) :: a -> AnonymousSlash b -> AnonymousSlash a #

Foldable AnonymousSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousSlash m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousSlash a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousSlash a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousSlash a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousSlash a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousSlash a -> b #

foldr1 :: (a -> a -> a) -> AnonymousSlash a -> a #

foldl1 :: (a -> a -> a) -> AnonymousSlash a -> a #

toList :: AnonymousSlash a -> [a] #

null :: AnonymousSlash a -> Bool #

length :: AnonymousSlash a -> Int #

elem :: Eq a => a -> AnonymousSlash a -> Bool #

maximum :: Ord a => AnonymousSlash a -> a #

minimum :: Ord a => AnonymousSlash a -> a #

sum :: Num a => AnonymousSlash a -> a #

product :: Num a => AnonymousSlash a -> a #

Traversable AnonymousSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousSlash a -> f (AnonymousSlash b) #

sequenceA :: Applicative f => AnonymousSlash (f a) -> f (AnonymousSlash a) #

mapM :: Monad m => (a -> m b) -> AnonymousSlash a -> m (AnonymousSlash b) #

sequence :: Monad m => AnonymousSlash (m a) -> m (AnonymousSlash a) #

SymbolMatching AnonymousSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousSlash a)

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 #

Generic1 AnonymousSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousSlash :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousSlash" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousPercent a Source #

Constructors

AnonymousPercent 

Fields

Instances
Functor AnonymousPercent Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousPercent a -> AnonymousPercent b #

(<$) :: a -> AnonymousPercent b -> AnonymousPercent a #

Foldable AnonymousPercent Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousPercent m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousPercent a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousPercent a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousPercent a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousPercent a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousPercent a -> b #

foldr1 :: (a -> a -> a) -> AnonymousPercent a -> a #

foldl1 :: (a -> a -> a) -> AnonymousPercent a -> a #

toList :: AnonymousPercent a -> [a] #

null :: AnonymousPercent a -> Bool #

length :: AnonymousPercent a -> Int #

elem :: Eq a => a -> AnonymousPercent a -> Bool #

maximum :: Ord a => AnonymousPercent a -> a #

minimum :: Ord a => AnonymousPercent a -> a #

sum :: Num a => AnonymousPercent a -> a #

product :: Num a => AnonymousPercent a -> a #

Traversable AnonymousPercent Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousPercent a -> f (AnonymousPercent b) #

sequenceA :: Applicative f => AnonymousPercent (f a) -> f (AnonymousPercent a) #

mapM :: Monad m => (a -> m b) -> AnonymousPercent a -> m (AnonymousPercent b) #

sequence :: Monad m => AnonymousPercent (m a) -> m (AnonymousPercent a) #

SymbolMatching AnonymousPercent Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousPercent Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousPercent a)

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 #

Generic1 AnonymousPercent Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousPercent :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousPercent" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousPercent Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousSlashSlash a Source #

Constructors

AnonymousSlashSlash 

Fields

Instances
Functor AnonymousSlashSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousSlashSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousSlashSlash m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousSlashSlash a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousSlashSlash a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousSlashSlash a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousSlashSlash a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousSlashSlash a -> b #

foldr1 :: (a -> a -> a) -> AnonymousSlashSlash a -> a #

foldl1 :: (a -> a -> a) -> AnonymousSlashSlash a -> a #

toList :: AnonymousSlashSlash a -> [a] #

null :: AnonymousSlashSlash a -> Bool #

length :: AnonymousSlashSlash a -> Int #

elem :: Eq a => a -> AnonymousSlashSlash a -> Bool #

maximum :: Ord a => AnonymousSlashSlash a -> a #

minimum :: Ord a => AnonymousSlashSlash a -> a #

sum :: Num a => AnonymousSlashSlash a -> a #

product :: Num a => AnonymousSlashSlash a -> a #

Traversable AnonymousSlashSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousSlashSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousSlashSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousSlashSlash a)

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 #

Generic1 AnonymousSlashSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousSlashSlash :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousSlashSlash" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousSlashSlash Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousStarStar a Source #

Constructors

AnonymousStarStar 

Fields

Instances
Functor AnonymousStarStar Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousStarStar Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousStarStar m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousStarStar a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousStarStar a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousStarStar a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousStarStar a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousStarStar a -> b #

foldr1 :: (a -> a -> a) -> AnonymousStarStar a -> a #

foldl1 :: (a -> a -> a) -> AnonymousStarStar a -> a #

toList :: AnonymousStarStar a -> [a] #

null :: AnonymousStarStar a -> Bool #

length :: AnonymousStarStar a -> Int #

elem :: Eq a => a -> AnonymousStarStar a -> Bool #

maximum :: Ord a => AnonymousStarStar a -> a #

minimum :: Ord a => AnonymousStarStar a -> a #

sum :: Num a => AnonymousStarStar a -> a #

product :: Num a => AnonymousStarStar a -> a #

Traversable AnonymousStarStar Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousStarStar a -> f (AnonymousStarStar b) #

sequenceA :: Applicative f => AnonymousStarStar (f a) -> f (AnonymousStarStar a) #

mapM :: Monad m => (a -> m b) -> AnonymousStarStar a -> m (AnonymousStarStar b) #

sequence :: Monad m => AnonymousStarStar (m a) -> m (AnonymousStarStar a) #

SymbolMatching AnonymousStarStar Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousStarStar Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousStarStar a)

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 #

Generic1 AnonymousStarStar Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousStarStar :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousStarStar" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousStarStar Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousPipe a Source #

Constructors

AnonymousPipe 

Fields

Instances
Functor AnonymousPipe Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousPipe a -> AnonymousPipe b #

(<$) :: a -> AnonymousPipe b -> AnonymousPipe a #

Foldable AnonymousPipe Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousPipe m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousPipe a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousPipe a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousPipe a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousPipe a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousPipe a -> b #

foldr1 :: (a -> a -> a) -> AnonymousPipe a -> a #

foldl1 :: (a -> a -> a) -> AnonymousPipe a -> a #

toList :: AnonymousPipe a -> [a] #

null :: AnonymousPipe a -> Bool #

length :: AnonymousPipe a -> Int #

elem :: Eq a => a -> AnonymousPipe a -> Bool #

maximum :: Ord a => AnonymousPipe a -> a #

minimum :: Ord a => AnonymousPipe a -> a #

sum :: Num a => AnonymousPipe a -> a #

product :: Num a => AnonymousPipe a -> a #

Traversable AnonymousPipe Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousPipe a -> f (AnonymousPipe b) #

sequenceA :: Applicative f => AnonymousPipe (f a) -> f (AnonymousPipe a) #

mapM :: Monad m => (a -> m b) -> AnonymousPipe a -> m (AnonymousPipe b) #

sequence :: Monad m => AnonymousPipe (m a) -> m (AnonymousPipe a) #

SymbolMatching AnonymousPipe Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousPipe Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousPipe a)

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 #

Generic1 AnonymousPipe Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousPipe :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousPipe" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousPipe Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousAmpersand a Source #

Constructors

AnonymousAmpersand 

Fields

Instances
Functor AnonymousAmpersand Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousAmpersand Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousAmpersand m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousAmpersand a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousAmpersand a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousAmpersand a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousAmpersand a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousAmpersand a -> b #

foldr1 :: (a -> a -> a) -> AnonymousAmpersand a -> a #

foldl1 :: (a -> a -> a) -> AnonymousAmpersand a -> a #

toList :: AnonymousAmpersand a -> [a] #

null :: AnonymousAmpersand a -> Bool #

length :: AnonymousAmpersand a -> Int #

elem :: Eq a => a -> AnonymousAmpersand a -> Bool #

maximum :: Ord a => AnonymousAmpersand a -> a #

minimum :: Ord a => AnonymousAmpersand a -> a #

sum :: Num a => AnonymousAmpersand a -> a #

product :: Num a => AnonymousAmpersand a -> a #

Traversable AnonymousAmpersand Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousAmpersand Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousAmpersand Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousAmpersand a)

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 #

Generic1 AnonymousAmpersand Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousAmpersand :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousAmpersand" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousAmpersand Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousCaret a Source #

Constructors

AnonymousCaret 

Fields

Instances
Functor AnonymousCaret Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousCaret a -> AnonymousCaret b #

(<$) :: a -> AnonymousCaret b -> AnonymousCaret a #

Foldable AnonymousCaret Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousCaret m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousCaret a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousCaret a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousCaret a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousCaret a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousCaret a -> b #

foldr1 :: (a -> a -> a) -> AnonymousCaret a -> a #

foldl1 :: (a -> a -> a) -> AnonymousCaret a -> a #

toList :: AnonymousCaret a -> [a] #

null :: AnonymousCaret a -> Bool #

length :: AnonymousCaret a -> Int #

elem :: Eq a => a -> AnonymousCaret a -> Bool #

maximum :: Ord a => AnonymousCaret a -> a #

minimum :: Ord a => AnonymousCaret a -> a #

sum :: Num a => AnonymousCaret a -> a #

product :: Num a => AnonymousCaret a -> a #

Traversable AnonymousCaret Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousCaret a -> f (AnonymousCaret b) #

sequenceA :: Applicative f => AnonymousCaret (f a) -> f (AnonymousCaret a) #

mapM :: Monad m => (a -> m b) -> AnonymousCaret a -> m (AnonymousCaret b) #

sequence :: Monad m => AnonymousCaret (m a) -> m (AnonymousCaret a) #

SymbolMatching AnonymousCaret Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousCaret Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousCaret a)

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 #

Generic1 AnonymousCaret Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousCaret :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousCaret" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousCaret Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousLAngleLAngle a Source #

Constructors

AnonymousLAngleLAngle 

Fields

Instances
Functor AnonymousLAngleLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousLAngleLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousLAngleLAngle m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousLAngleLAngle a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousLAngleLAngle a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousLAngleLAngle a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousLAngleLAngle a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousLAngleLAngle a -> b #

foldr1 :: (a -> a -> a) -> AnonymousLAngleLAngle a -> a #

foldl1 :: (a -> a -> a) -> AnonymousLAngleLAngle a -> a #

toList :: AnonymousLAngleLAngle a -> [a] #

null :: AnonymousLAngleLAngle a -> Bool #

length :: AnonymousLAngleLAngle a -> Int #

elem :: Eq a => a -> AnonymousLAngleLAngle a -> Bool #

maximum :: Ord a => AnonymousLAngleLAngle a -> a #

minimum :: Ord a => AnonymousLAngleLAngle a -> a #

sum :: Num a => AnonymousLAngleLAngle a -> a #

product :: Num a => AnonymousLAngleLAngle a -> a #

Traversable AnonymousLAngleLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousLAngleLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousLAngleLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousLAngleLAngle a)

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 #

Generic1 AnonymousLAngleLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousLAngleLAngle :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousLAngleLAngle" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousLAngleLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousTilde a Source #

Constructors

AnonymousTilde 

Fields

Instances
Functor AnonymousTilde Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousTilde a -> AnonymousTilde b #

(<$) :: a -> AnonymousTilde b -> AnonymousTilde a #

Foldable AnonymousTilde Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousTilde m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousTilde a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousTilde a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousTilde a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousTilde a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousTilde a -> b #

foldr1 :: (a -> a -> a) -> AnonymousTilde a -> a #

foldl1 :: (a -> a -> a) -> AnonymousTilde a -> a #

toList :: AnonymousTilde a -> [a] #

null :: AnonymousTilde a -> Bool #

length :: AnonymousTilde a -> Int #

elem :: Eq a => a -> AnonymousTilde a -> Bool #

maximum :: Ord a => AnonymousTilde a -> a #

minimum :: Ord a => AnonymousTilde a -> a #

sum :: Num a => AnonymousTilde a -> a #

product :: Num a => AnonymousTilde a -> a #

Traversable AnonymousTilde Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousTilde a -> f (AnonymousTilde b) #

sequenceA :: Applicative f => AnonymousTilde (f a) -> f (AnonymousTilde a) #

mapM :: Monad m => (a -> m b) -> AnonymousTilde a -> m (AnonymousTilde b) #

sequence :: Monad m => AnonymousTilde (m a) -> m (AnonymousTilde a) #

SymbolMatching AnonymousTilde Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousTilde Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousTilde a)

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 #

Generic1 AnonymousTilde Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousTilde :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousTilde" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousTilde Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousLAngle a Source #

Constructors

AnonymousLAngle 

Fields

Instances
Functor AnonymousLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousLAngle a -> AnonymousLAngle b #

(<$) :: a -> AnonymousLAngle b -> AnonymousLAngle a #

Foldable AnonymousLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousLAngle m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousLAngle a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousLAngle a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousLAngle a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousLAngle a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousLAngle a -> b #

foldr1 :: (a -> a -> a) -> AnonymousLAngle a -> a #

foldl1 :: (a -> a -> a) -> AnonymousLAngle a -> a #

toList :: AnonymousLAngle a -> [a] #

null :: AnonymousLAngle a -> Bool #

length :: AnonymousLAngle a -> Int #

elem :: Eq a => a -> AnonymousLAngle a -> Bool #

maximum :: Ord a => AnonymousLAngle a -> a #

minimum :: Ord a => AnonymousLAngle a -> a #

sum :: Num a => AnonymousLAngle a -> a #

product :: Num a => AnonymousLAngle a -> a #

Traversable AnonymousLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousLAngle a -> f (AnonymousLAngle b) #

sequenceA :: Applicative f => AnonymousLAngle (f a) -> f (AnonymousLAngle a) #

mapM :: Monad m => (a -> m b) -> AnonymousLAngle a -> m (AnonymousLAngle b) #

sequence :: Monad m => AnonymousLAngle (m a) -> m (AnonymousLAngle a) #

SymbolMatching AnonymousLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousLAngle a)

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 #

Generic1 AnonymousLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousLAngle :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousLAngle" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousLAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousLAngleEqual a Source #

Constructors

AnonymousLAngleEqual 

Fields

Instances
Functor AnonymousLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousLAngleEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousLAngleEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousLAngleEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousLAngleEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousLAngleEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousLAngleEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousLAngleEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousLAngleEqual a -> a #

toList :: AnonymousLAngleEqual a -> [a] #

null :: AnonymousLAngleEqual a -> Bool #

length :: AnonymousLAngleEqual a -> Int #

elem :: Eq a => a -> AnonymousLAngleEqual a -> Bool #

maximum :: Ord a => AnonymousLAngleEqual a -> a #

minimum :: Ord a => AnonymousLAngleEqual a -> a #

sum :: Num a => AnonymousLAngleEqual a -> a #

product :: Num a => AnonymousLAngleEqual a -> a #

Traversable AnonymousLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousLAngleEqual a)

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 #

Generic1 AnonymousLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousLAngleEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousLAngleEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousEqualEqual a Source #

Constructors

AnonymousEqualEqual 

Fields

Instances
Functor AnonymousEqualEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousEqualEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousEqualEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousEqualEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousEqualEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousEqualEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousEqualEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousEqualEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousEqualEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousEqualEqual a -> a #

toList :: AnonymousEqualEqual a -> [a] #

null :: AnonymousEqualEqual a -> Bool #

length :: AnonymousEqualEqual a -> Int #

elem :: Eq a => a -> AnonymousEqualEqual a -> Bool #

maximum :: Ord a => AnonymousEqualEqual a -> a #

minimum :: Ord a => AnonymousEqualEqual a -> a #

sum :: Num a => AnonymousEqualEqual a -> a #

product :: Num a => AnonymousEqualEqual a -> a #

Traversable AnonymousEqualEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousEqualEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousEqualEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousEqualEqual a)

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 #

Generic1 AnonymousEqualEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousEqualEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousEqualEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousEqualEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousBangEqual a Source #

Constructors

AnonymousBangEqual 

Fields

Instances
Functor AnonymousBangEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousBangEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousBangEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousBangEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousBangEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousBangEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousBangEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousBangEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousBangEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousBangEqual a -> a #

toList :: AnonymousBangEqual a -> [a] #

null :: AnonymousBangEqual a -> Bool #

length :: AnonymousBangEqual a -> Int #

elem :: Eq a => a -> AnonymousBangEqual a -> Bool #

maximum :: Ord a => AnonymousBangEqual a -> a #

minimum :: Ord a => AnonymousBangEqual a -> a #

sum :: Num a => AnonymousBangEqual a -> a #

product :: Num a => AnonymousBangEqual a -> a #

Traversable AnonymousBangEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousBangEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousBangEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousBangEqual a)

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 #

Generic1 AnonymousBangEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousBangEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousBangEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousBangEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousRAngleEqual a Source #

Constructors

AnonymousRAngleEqual 

Fields

Instances
Functor AnonymousRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousRAngleEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousRAngleEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousRAngleEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousRAngleEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousRAngleEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousRAngleEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousRAngleEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousRAngleEqual a -> a #

toList :: AnonymousRAngleEqual a -> [a] #

null :: AnonymousRAngleEqual a -> Bool #

length :: AnonymousRAngleEqual a -> Int #

elem :: Eq a => a -> AnonymousRAngleEqual a -> Bool #

maximum :: Ord a => AnonymousRAngleEqual a -> a #

minimum :: Ord a => AnonymousRAngleEqual a -> a #

sum :: Num a => AnonymousRAngleEqual a -> a #

product :: Num a => AnonymousRAngleEqual a -> a #

Traversable AnonymousRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousRAngleEqual a)

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 #

Generic1 AnonymousRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousRAngleEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousRAngleEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousRAngle a Source #

Constructors

AnonymousRAngle 

Fields

Instances
Functor AnonymousRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousRAngle a -> AnonymousRAngle b #

(<$) :: a -> AnonymousRAngle b -> AnonymousRAngle a #

Foldable AnonymousRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousRAngle m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousRAngle a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousRAngle a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousRAngle a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousRAngle a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousRAngle a -> b #

foldr1 :: (a -> a -> a) -> AnonymousRAngle a -> a #

foldl1 :: (a -> a -> a) -> AnonymousRAngle a -> a #

toList :: AnonymousRAngle a -> [a] #

null :: AnonymousRAngle a -> Bool #

length :: AnonymousRAngle a -> Int #

elem :: Eq a => a -> AnonymousRAngle a -> Bool #

maximum :: Ord a => AnonymousRAngle a -> a #

minimum :: Ord a => AnonymousRAngle a -> a #

sum :: Num a => AnonymousRAngle a -> a #

product :: Num a => AnonymousRAngle a -> a #

Traversable AnonymousRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousRAngle a -> f (AnonymousRAngle b) #

sequenceA :: Applicative f => AnonymousRAngle (f a) -> f (AnonymousRAngle a) #

mapM :: Monad m => (a -> m b) -> AnonymousRAngle a -> m (AnonymousRAngle b) #

sequence :: Monad m => AnonymousRAngle (m a) -> m (AnonymousRAngle a) #

SymbolMatching AnonymousRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousRAngle a)

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 #

Generic1 AnonymousRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousRAngle :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousRAngle" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousLAngleRAngle a Source #

Constructors

AnonymousLAngleRAngle 

Fields

Instances
Functor AnonymousLAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousLAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousLAngleRAngle m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousLAngleRAngle a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousLAngleRAngle a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousLAngleRAngle a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousLAngleRAngle a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousLAngleRAngle a -> b #

foldr1 :: (a -> a -> a) -> AnonymousLAngleRAngle a -> a #

foldl1 :: (a -> a -> a) -> AnonymousLAngleRAngle a -> a #

toList :: AnonymousLAngleRAngle a -> [a] #

null :: AnonymousLAngleRAngle a -> Bool #

length :: AnonymousLAngleRAngle a -> Int #

elem :: Eq a => a -> AnonymousLAngleRAngle a -> Bool #

maximum :: Ord a => AnonymousLAngleRAngle a -> a #

minimum :: Ord a => AnonymousLAngleRAngle a -> a #

sum :: Num a => AnonymousLAngleRAngle a -> a #

product :: Num a => AnonymousLAngleRAngle a -> a #

Traversable AnonymousLAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousLAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousLAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousLAngleRAngle a)

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 #

Generic1 AnonymousLAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousLAngleRAngle :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousLAngleRAngle" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousLAngleRAngle Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousIs a Source #

Constructors

AnonymousIs 

Fields

Instances
Functor AnonymousIs Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousIs a -> AnonymousIs b #

(<$) :: a -> AnonymousIs b -> AnonymousIs a #

Foldable AnonymousIs Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousIs m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousIs a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousIs a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousIs a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousIs a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousIs a -> b #

foldr1 :: (a -> a -> a) -> AnonymousIs a -> a #

foldl1 :: (a -> a -> a) -> AnonymousIs a -> a #

toList :: AnonymousIs a -> [a] #

null :: AnonymousIs a -> Bool #

length :: AnonymousIs a -> Int #

elem :: Eq a => a -> AnonymousIs a -> Bool #

maximum :: Ord a => AnonymousIs a -> a #

minimum :: Ord a => AnonymousIs a -> a #

sum :: Num a => AnonymousIs a -> a #

product :: Num a => AnonymousIs a -> a #

Traversable AnonymousIs Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousIs a -> f (AnonymousIs b) #

sequenceA :: Applicative f => AnonymousIs (f a) -> f (AnonymousIs a) #

mapM :: Monad m => (a -> m b) -> AnonymousIs a -> m (AnonymousIs b) #

sequence :: Monad m => AnonymousIs (m a) -> m (AnonymousIs a) #

SymbolMatching AnonymousIs Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousIs Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousIs a)

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 #

Generic1 AnonymousIs Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousIs :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousIs" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousIs Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousLambda a Source #

Constructors

AnonymousLambda 

Fields

Instances
Functor AnonymousLambda Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousLambda a -> AnonymousLambda b #

(<$) :: a -> AnonymousLambda b -> AnonymousLambda a #

Foldable AnonymousLambda Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousLambda m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousLambda a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousLambda a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousLambda a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousLambda a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousLambda a -> b #

foldr1 :: (a -> a -> a) -> AnonymousLambda a -> a #

foldl1 :: (a -> a -> a) -> AnonymousLambda a -> a #

toList :: AnonymousLambda a -> [a] #

null :: AnonymousLambda a -> Bool #

length :: AnonymousLambda a -> Int #

elem :: Eq a => a -> AnonymousLambda a -> Bool #

maximum :: Ord a => AnonymousLambda a -> a #

minimum :: Ord a => AnonymousLambda a -> a #

sum :: Num a => AnonymousLambda a -> a #

product :: Num a => AnonymousLambda a -> a #

Traversable AnonymousLambda Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousLambda a -> f (AnonymousLambda b) #

sequenceA :: Applicative f => AnonymousLambda (f a) -> f (AnonymousLambda a) #

mapM :: Monad m => (a -> m b) -> AnonymousLambda a -> m (AnonymousLambda b) #

sequence :: Monad m => AnonymousLambda (m a) -> m (AnonymousLambda a) #

SymbolMatching AnonymousLambda Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousLambda Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousLambda a)

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 #

Generic1 AnonymousLambda Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousLambda :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousLambda" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousLambda Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousPlusEqual a Source #

Constructors

AnonymousPlusEqual 

Fields

Instances
Functor AnonymousPlusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousPlusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousPlusEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousPlusEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousPlusEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousPlusEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousPlusEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousPlusEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousPlusEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousPlusEqual a -> a #

toList :: AnonymousPlusEqual a -> [a] #

null :: AnonymousPlusEqual a -> Bool #

length :: AnonymousPlusEqual a -> Int #

elem :: Eq a => a -> AnonymousPlusEqual a -> Bool #

maximum :: Ord a => AnonymousPlusEqual a -> a #

minimum :: Ord a => AnonymousPlusEqual a -> a #

sum :: Num a => AnonymousPlusEqual a -> a #

product :: Num a => AnonymousPlusEqual a -> a #

Traversable AnonymousPlusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousPlusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousPlusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousPlusEqual a)

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 #

Generic1 AnonymousPlusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousPlusEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousPlusEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousPlusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousMinusEqual a Source #

Constructors

AnonymousMinusEqual 

Fields

Instances
Functor AnonymousMinusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousMinusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousMinusEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousMinusEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousMinusEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousMinusEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousMinusEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousMinusEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousMinusEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousMinusEqual a -> a #

toList :: AnonymousMinusEqual a -> [a] #

null :: AnonymousMinusEqual a -> Bool #

length :: AnonymousMinusEqual a -> Int #

elem :: Eq a => a -> AnonymousMinusEqual a -> Bool #

maximum :: Ord a => AnonymousMinusEqual a -> a #

minimum :: Ord a => AnonymousMinusEqual a -> a #

sum :: Num a => AnonymousMinusEqual a -> a #

product :: Num a => AnonymousMinusEqual a -> a #

Traversable AnonymousMinusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousMinusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousMinusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousMinusEqual a)

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 #

Generic1 AnonymousMinusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousMinusEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousMinusEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousMinusEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousStarEqual a Source #

Constructors

AnonymousStarEqual 

Fields

Instances
Functor AnonymousStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousStarEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousStarEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousStarEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousStarEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousStarEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousStarEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousStarEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousStarEqual a -> a #

toList :: AnonymousStarEqual a -> [a] #

null :: AnonymousStarEqual a -> Bool #

length :: AnonymousStarEqual a -> Int #

elem :: Eq a => a -> AnonymousStarEqual a -> Bool #

maximum :: Ord a => AnonymousStarEqual a -> a #

minimum :: Ord a => AnonymousStarEqual a -> a #

sum :: Num a => AnonymousStarEqual a -> a #

product :: Num a => AnonymousStarEqual a -> a #

Traversable AnonymousStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousStarEqual a)

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 #

Generic1 AnonymousStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousStarEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousStarEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousSlashEqual a Source #

Constructors

AnonymousSlashEqual 

Fields

Instances
Functor AnonymousSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousSlashEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousSlashEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousSlashEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousSlashEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousSlashEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousSlashEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousSlashEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousSlashEqual a -> a #

toList :: AnonymousSlashEqual a -> [a] #

null :: AnonymousSlashEqual a -> Bool #

length :: AnonymousSlashEqual a -> Int #

elem :: Eq a => a -> AnonymousSlashEqual a -> Bool #

maximum :: Ord a => AnonymousSlashEqual a -> a #

minimum :: Ord a => AnonymousSlashEqual a -> a #

sum :: Num a => AnonymousSlashEqual a -> a #

product :: Num a => AnonymousSlashEqual a -> a #

Traversable AnonymousSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousSlashEqual a)

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 #

Generic1 AnonymousSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousSlashEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousSlashEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousAtEqual a Source #

Constructors

AnonymousAtEqual 

Fields

Instances
Functor AnonymousAtEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousAtEqual a -> AnonymousAtEqual b #

(<$) :: a -> AnonymousAtEqual b -> AnonymousAtEqual a #

Foldable AnonymousAtEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousAtEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousAtEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousAtEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousAtEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousAtEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousAtEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousAtEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousAtEqual a -> a #

toList :: AnonymousAtEqual a -> [a] #

null :: AnonymousAtEqual a -> Bool #

length :: AnonymousAtEqual a -> Int #

elem :: Eq a => a -> AnonymousAtEqual a -> Bool #

maximum :: Ord a => AnonymousAtEqual a -> a #

minimum :: Ord a => AnonymousAtEqual a -> a #

sum :: Num a => AnonymousAtEqual a -> a #

product :: Num a => AnonymousAtEqual a -> a #

Traversable AnonymousAtEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousAtEqual a -> f (AnonymousAtEqual b) #

sequenceA :: Applicative f => AnonymousAtEqual (f a) -> f (AnonymousAtEqual a) #

mapM :: Monad m => (a -> m b) -> AnonymousAtEqual a -> m (AnonymousAtEqual b) #

sequence :: Monad m => AnonymousAtEqual (m a) -> m (AnonymousAtEqual a) #

SymbolMatching AnonymousAtEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousAtEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousAtEqual a)

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 #

Generic1 AnonymousAtEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousAtEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousAtEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousAtEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousSlashSlashEqual a Source #

Constructors

AnonymousSlashSlashEqual 

Fields

Instances
Functor AnonymousSlashSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousSlashSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousSlashSlashEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousSlashSlashEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousSlashSlashEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousSlashSlashEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousSlashSlashEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousSlashSlashEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousSlashSlashEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousSlashSlashEqual a -> a #

toList :: AnonymousSlashSlashEqual a -> [a] #

null :: AnonymousSlashSlashEqual a -> Bool #

length :: AnonymousSlashSlashEqual a -> Int #

elem :: Eq a => a -> AnonymousSlashSlashEqual a -> Bool #

maximum :: Ord a => AnonymousSlashSlashEqual a -> a #

minimum :: Ord a => AnonymousSlashSlashEqual a -> a #

sum :: Num a => AnonymousSlashSlashEqual a -> a #

product :: Num a => AnonymousSlashSlashEqual a -> a #

Traversable AnonymousSlashSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousSlashSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousSlashSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousSlashSlashEqual a)

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 #

Generic1 AnonymousSlashSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousSlashSlashEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousSlashSlashEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousSlashSlashEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousPercentEqual a Source #

Constructors

AnonymousPercentEqual 

Fields

Instances
Functor AnonymousPercentEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousPercentEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousPercentEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousPercentEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousPercentEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousPercentEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousPercentEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousPercentEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousPercentEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousPercentEqual a -> a #

toList :: AnonymousPercentEqual a -> [a] #

null :: AnonymousPercentEqual a -> Bool #

length :: AnonymousPercentEqual a -> Int #

elem :: Eq a => a -> AnonymousPercentEqual a -> Bool #

maximum :: Ord a => AnonymousPercentEqual a -> a #

minimum :: Ord a => AnonymousPercentEqual a -> a #

sum :: Num a => AnonymousPercentEqual a -> a #

product :: Num a => AnonymousPercentEqual a -> a #

Traversable AnonymousPercentEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousPercentEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousPercentEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousPercentEqual a)

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 #

Generic1 AnonymousPercentEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousPercentEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousPercentEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousPercentEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousStarStarEqual a Source #

Constructors

AnonymousStarStarEqual 

Fields

Instances
Functor AnonymousStarStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousStarStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousStarStarEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousStarStarEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousStarStarEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousStarStarEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousStarStarEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousStarStarEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousStarStarEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousStarStarEqual a -> a #

toList :: AnonymousStarStarEqual a -> [a] #

null :: AnonymousStarStarEqual a -> Bool #

length :: AnonymousStarStarEqual a -> Int #

elem :: Eq a => a -> AnonymousStarStarEqual a -> Bool #

maximum :: Ord a => AnonymousStarStarEqual a -> a #

minimum :: Ord a => AnonymousStarStarEqual a -> a #

sum :: Num a => AnonymousStarStarEqual a -> a #

product :: Num a => AnonymousStarStarEqual a -> a #

Traversable AnonymousStarStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousStarStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousStarStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousStarStarEqual a)

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 #

Generic1 AnonymousStarStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousStarStarEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousStarStarEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousStarStarEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousRAngleRAngleEqual a Source #

Constructors

AnonymousRAngleRAngleEqual 

Fields

Instances
Functor AnonymousRAngleRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousRAngleRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousRAngleRAngleEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousRAngleRAngleEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousRAngleRAngleEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousRAngleRAngleEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousRAngleRAngleEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousRAngleRAngleEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousRAngleRAngleEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousRAngleRAngleEqual a -> a #

toList :: AnonymousRAngleRAngleEqual a -> [a] #

null :: AnonymousRAngleRAngleEqual a -> Bool #

length :: AnonymousRAngleRAngleEqual a -> Int #

elem :: Eq a => a -> AnonymousRAngleRAngleEqual a -> Bool #

maximum :: Ord a => AnonymousRAngleRAngleEqual a -> a #

minimum :: Ord a => AnonymousRAngleRAngleEqual a -> a #

sum :: Num a => AnonymousRAngleRAngleEqual a -> a #

product :: Num a => AnonymousRAngleRAngleEqual a -> a #

Traversable AnonymousRAngleRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousRAngleRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousRAngleRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousRAngleRAngleEqual a)

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 #

Generic1 AnonymousRAngleRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousRAngleRAngleEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousRAngleRAngleEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousRAngleRAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousLAngleLAngleEqual a Source #

Constructors

AnonymousLAngleLAngleEqual 

Fields

Instances
Functor AnonymousLAngleLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousLAngleLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousLAngleLAngleEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousLAngleLAngleEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousLAngleLAngleEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousLAngleLAngleEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousLAngleLAngleEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousLAngleLAngleEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousLAngleLAngleEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousLAngleLAngleEqual a -> a #

toList :: AnonymousLAngleLAngleEqual a -> [a] #

null :: AnonymousLAngleLAngleEqual a -> Bool #

length :: AnonymousLAngleLAngleEqual a -> Int #

elem :: Eq a => a -> AnonymousLAngleLAngleEqual a -> Bool #

maximum :: Ord a => AnonymousLAngleLAngleEqual a -> a #

minimum :: Ord a => AnonymousLAngleLAngleEqual a -> a #

sum :: Num a => AnonymousLAngleLAngleEqual a -> a #

product :: Num a => AnonymousLAngleLAngleEqual a -> a #

Traversable AnonymousLAngleLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousLAngleLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousLAngleLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousLAngleLAngleEqual a)

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 #

Generic1 AnonymousLAngleLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousLAngleLAngleEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousLAngleLAngleEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousLAngleLAngleEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousAmpersandEqual a Source #

Constructors

AnonymousAmpersandEqual 

Fields

Instances
Functor AnonymousAmpersandEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousAmpersandEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousAmpersandEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousAmpersandEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousAmpersandEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousAmpersandEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousAmpersandEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousAmpersandEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousAmpersandEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousAmpersandEqual a -> a #

toList :: AnonymousAmpersandEqual a -> [a] #

null :: AnonymousAmpersandEqual a -> Bool #

length :: AnonymousAmpersandEqual a -> Int #

elem :: Eq a => a -> AnonymousAmpersandEqual a -> Bool #

maximum :: Ord a => AnonymousAmpersandEqual a -> a #

minimum :: Ord a => AnonymousAmpersandEqual a -> a #

sum :: Num a => AnonymousAmpersandEqual a -> a #

product :: Num a => AnonymousAmpersandEqual a -> a #

Traversable AnonymousAmpersandEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousAmpersandEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousAmpersandEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousAmpersandEqual a)

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 #

Generic1 AnonymousAmpersandEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousAmpersandEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousAmpersandEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousAmpersandEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousCaretEqual a Source #

Constructors

AnonymousCaretEqual 

Fields

Instances
Functor AnonymousCaretEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousCaretEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousCaretEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousCaretEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousCaretEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousCaretEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousCaretEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousCaretEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousCaretEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousCaretEqual a -> a #

toList :: AnonymousCaretEqual a -> [a] #

null :: AnonymousCaretEqual a -> Bool #

length :: AnonymousCaretEqual a -> Int #

elem :: Eq a => a -> AnonymousCaretEqual a -> Bool #

maximum :: Ord a => AnonymousCaretEqual a -> a #

minimum :: Ord a => AnonymousCaretEqual a -> a #

sum :: Num a => AnonymousCaretEqual a -> a #

product :: Num a => AnonymousCaretEqual a -> a #

Traversable AnonymousCaretEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousCaretEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousCaretEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousCaretEqual a)

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 #

Generic1 AnonymousCaretEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousCaretEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousCaretEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousCaretEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousPipeEqual a Source #

Constructors

AnonymousPipeEqual 

Fields

Instances
Functor AnonymousPipeEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousPipeEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousPipeEqual m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousPipeEqual a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousPipeEqual a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousPipeEqual a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousPipeEqual a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousPipeEqual a -> b #

foldr1 :: (a -> a -> a) -> AnonymousPipeEqual a -> a #

foldl1 :: (a -> a -> a) -> AnonymousPipeEqual a -> a #

toList :: AnonymousPipeEqual a -> [a] #

null :: AnonymousPipeEqual a -> Bool #

length :: AnonymousPipeEqual a -> Int #

elem :: Eq a => a -> AnonymousPipeEqual a -> Bool #

maximum :: Ord a => AnonymousPipeEqual a -> a #

minimum :: Ord a => AnonymousPipeEqual a -> a #

sum :: Num a => AnonymousPipeEqual a -> a #

product :: Num a => AnonymousPipeEqual a -> a #

Traversable AnonymousPipeEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AnonymousPipeEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousPipeEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousPipeEqual a)

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 #

Generic1 AnonymousPipeEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousPipeEqual :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousPipeEqual" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousPipeEqual Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousYield a Source #

Constructors

AnonymousYield 

Fields

Instances
Functor AnonymousYield Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousYield a -> AnonymousYield b #

(<$) :: a -> AnonymousYield b -> AnonymousYield a #

Foldable AnonymousYield Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousYield m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousYield a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousYield a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousYield a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousYield a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousYield a -> b #

foldr1 :: (a -> a -> a) -> AnonymousYield a -> a #

foldl1 :: (a -> a -> a) -> AnonymousYield a -> a #

toList :: AnonymousYield a -> [a] #

null :: AnonymousYield a -> Bool #

length :: AnonymousYield a -> Int #

elem :: Eq a => a -> AnonymousYield a -> Bool #

maximum :: Ord a => AnonymousYield a -> a #

minimum :: Ord a => AnonymousYield a -> a #

sum :: Num a => AnonymousYield a -> a #

product :: Num a => AnonymousYield a -> a #

Traversable AnonymousYield Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousYield a -> f (AnonymousYield b) #

sequenceA :: Applicative f => AnonymousYield (f a) -> f (AnonymousYield a) #

mapM :: Monad m => (a -> m b) -> AnonymousYield a -> m (AnonymousYield b) #

sequence :: Monad m => AnonymousYield (m a) -> m (AnonymousYield a) #

SymbolMatching AnonymousYield Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousYield Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousYield a)

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 #

Generic1 AnonymousYield Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousYield :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousYield" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousYield Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousLBracket a Source #

Constructors

AnonymousLBracket 

Fields

Instances
Functor AnonymousLBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousLBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousLBracket m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousLBracket a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousLBracket a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousLBracket a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousLBracket a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousLBracket a -> b #

foldr1 :: (a -> a -> a) -> AnonymousLBracket a -> a #

foldl1 :: (a -> a -> a) -> AnonymousLBracket a -> a #

toList :: AnonymousLBracket a -> [a] #

null :: AnonymousLBracket a -> Bool #

length :: AnonymousLBracket a -> Int #

elem :: Eq a => a -> AnonymousLBracket a -> Bool #

maximum :: Ord a => AnonymousLBracket a -> a #

minimum :: Ord a => AnonymousLBracket a -> a #

sum :: Num a => AnonymousLBracket a -> a #

product :: Num a => AnonymousLBracket a -> a #

Traversable AnonymousLBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousLBracket a -> f (AnonymousLBracket b) #

sequenceA :: Applicative f => AnonymousLBracket (f a) -> f (AnonymousLBracket a) #

mapM :: Monad m => (a -> m b) -> AnonymousLBracket a -> m (AnonymousLBracket b) #

sequence :: Monad m => AnonymousLBracket (m a) -> m (AnonymousLBracket a) #

SymbolMatching AnonymousLBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousLBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousLBracket a)

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 #

Generic1 AnonymousLBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousLBracket :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousLBracket" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousLBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousRBracket a Source #

Constructors

AnonymousRBracket 

Fields

Instances
Functor AnonymousRBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AnonymousRBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousRBracket m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousRBracket a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousRBracket a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousRBracket a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousRBracket a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousRBracket a -> b #

foldr1 :: (a -> a -> a) -> AnonymousRBracket a -> a #

foldl1 :: (a -> a -> a) -> AnonymousRBracket a -> a #

toList :: AnonymousRBracket a -> [a] #

null :: AnonymousRBracket a -> Bool #

length :: AnonymousRBracket a -> Int #

elem :: Eq a => a -> AnonymousRBracket a -> Bool #

maximum :: Ord a => AnonymousRBracket a -> a #

minimum :: Ord a => AnonymousRBracket a -> a #

sum :: Num a => AnonymousRBracket a -> a #

product :: Num a => AnonymousRBracket a -> a #

Traversable AnonymousRBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousRBracket a -> f (AnonymousRBracket b) #

sequenceA :: Applicative f => AnonymousRBracket (f a) -> f (AnonymousRBracket a) #

mapM :: Monad m => (a -> m b) -> AnonymousRBracket a -> m (AnonymousRBracket b) #

sequence :: Monad m => AnonymousRBracket (m a) -> m (AnonymousRBracket a) #

SymbolMatching AnonymousRBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousRBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousRBracket a)

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 #

Generic1 AnonymousRBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousRBracket :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousRBracket" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousRBracket Source # 
Instance details

Defined in TreeSitter.Python.AST

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

data Ellipsis a Source #

Constructors

Ellipsis 

Fields

Instances
Functor Ellipsis Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Ellipsis a -> Ellipsis b #

(<$) :: a -> Ellipsis b -> Ellipsis a #

Foldable Ellipsis Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Ellipsis m -> m #

foldMap :: Monoid m => (a -> m) -> Ellipsis a -> m #

foldr :: (a -> b -> b) -> b -> Ellipsis a -> b #

foldr' :: (a -> b -> b) -> b -> Ellipsis a -> b #

foldl :: (b -> a -> b) -> b -> Ellipsis a -> b #

foldl' :: (b -> a -> b) -> b -> Ellipsis a -> b #

foldr1 :: (a -> a -> a) -> Ellipsis a -> a #

foldl1 :: (a -> a -> a) -> Ellipsis a -> a #

toList :: Ellipsis a -> [a] #

null :: Ellipsis a -> Bool #

length :: Ellipsis a -> Int #

elem :: Eq a => a -> Ellipsis a -> Bool #

maximum :: Ord a => Ellipsis a -> a #

minimum :: Ord a => Ellipsis a -> a #

sum :: Num a => Ellipsis a -> a #

product :: Num a => Ellipsis a -> a #

Traversable Ellipsis Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Ellipsis a -> f (Ellipsis b) #

sequenceA :: Applicative f => Ellipsis (f a) -> f (Ellipsis a) #

mapM :: Monad m => (a -> m b) -> Ellipsis a -> m (Ellipsis b) #

sequence :: Monad m => Ellipsis (m a) -> m (Ellipsis a) #

SymbolMatching Ellipsis Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Ellipsis -> Node -> Bool

showFailure :: Proxy Ellipsis -> Node -> String

Unmarshal Ellipsis Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Ellipsis a)

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 #

Generic1 Ellipsis Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Ellipsis :: k -> Type #

Methods

from1 :: Ellipsis a -> Rep1 Ellipsis a #

to1 :: Rep1 Ellipsis a -> Ellipsis a #

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.5.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)))
type Rep1 Ellipsis Source # 
Instance details

Defined in TreeSitter.Python.AST

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

newtype AnonymousLBrace a Source #

Constructors

AnonymousLBrace 

Fields

Instances
Functor AnonymousLBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousLBrace a -> AnonymousLBrace b #

(<$) :: a -> AnonymousLBrace b -> AnonymousLBrace a #

Foldable AnonymousLBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousLBrace m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousLBrace a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousLBrace a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousLBrace a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousLBrace a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousLBrace a -> b #

foldr1 :: (a -> a -> a) -> AnonymousLBrace a -> a #

foldl1 :: (a -> a -> a) -> AnonymousLBrace a -> a #

toList :: AnonymousLBrace a -> [a] #

null :: AnonymousLBrace a -> Bool #

length :: AnonymousLBrace a -> Int #

elem :: Eq a => a -> AnonymousLBrace a -> Bool #

maximum :: Ord a => AnonymousLBrace a -> a #

minimum :: Ord a => AnonymousLBrace a -> a #

sum :: Num a => AnonymousLBrace a -> a #

product :: Num a => AnonymousLBrace a -> a #

Traversable AnonymousLBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousLBrace a -> f (AnonymousLBrace b) #

sequenceA :: Applicative f => AnonymousLBrace (f a) -> f (AnonymousLBrace a) #

mapM :: Monad m => (a -> m b) -> AnonymousLBrace a -> m (AnonymousLBrace b) #

sequence :: Monad m => AnonymousLBrace (m a) -> m (AnonymousLBrace a) #

SymbolMatching AnonymousLBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousLBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousLBrace a)

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 #

Generic1 AnonymousLBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousLBrace :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousLBrace" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousLBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 AnonymousLBrace = D1 (MetaData "AnonymousLBrace" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" True) (C1 (MetaCons "AnonymousLBrace" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype AnonymousRBrace a Source #

Constructors

AnonymousRBrace 

Fields

Instances
Functor AnonymousRBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousRBrace a -> AnonymousRBrace b #

(<$) :: a -> AnonymousRBrace b -> AnonymousRBrace a #

Foldable AnonymousRBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousRBrace m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousRBrace a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousRBrace a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousRBrace a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousRBrace a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousRBrace a -> b #

foldr1 :: (a -> a -> a) -> AnonymousRBrace a -> a #

foldl1 :: (a -> a -> a) -> AnonymousRBrace a -> a #

toList :: AnonymousRBrace a -> [a] #

null :: AnonymousRBrace a -> Bool #

length :: AnonymousRBrace a -> Int #

elem :: Eq a => a -> AnonymousRBrace a -> Bool #

maximum :: Ord a => AnonymousRBrace a -> a #

minimum :: Ord a => AnonymousRBrace a -> a #

sum :: Num a => AnonymousRBrace a -> a #

product :: Num a => AnonymousRBrace a -> a #

Traversable AnonymousRBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousRBrace a -> f (AnonymousRBrace b) #

sequenceA :: Applicative f => AnonymousRBrace (f a) -> f (AnonymousRBrace a) #

mapM :: Monad m => (a -> m b) -> AnonymousRBrace a -> m (AnonymousRBrace b) #

sequence :: Monad m => AnonymousRBrace (m a) -> m (AnonymousRBrace a) #

SymbolMatching AnonymousRBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousRBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousRBrace a)

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 #

Generic1 AnonymousRBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousRBrace :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousRBrace" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousRBrace Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 AnonymousRBrace = D1 (MetaData "AnonymousRBrace" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" True) (C1 (MetaCons "AnonymousRBrace" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

data EscapeSequence a Source #

Constructors

EscapeSequence 

Fields

Instances
Functor EscapeSequence Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> EscapeSequence a -> EscapeSequence b #

(<$) :: a -> EscapeSequence b -> EscapeSequence a #

Foldable EscapeSequence Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => EscapeSequence m -> m #

foldMap :: Monoid m => (a -> m) -> EscapeSequence a -> m #

foldr :: (a -> b -> b) -> b -> EscapeSequence a -> b #

foldr' :: (a -> b -> b) -> b -> EscapeSequence a -> b #

foldl :: (b -> a -> b) -> b -> EscapeSequence a -> b #

foldl' :: (b -> a -> b) -> b -> EscapeSequence a -> b #

foldr1 :: (a -> a -> a) -> EscapeSequence a -> a #

foldl1 :: (a -> a -> a) -> EscapeSequence a -> a #

toList :: EscapeSequence a -> [a] #

null :: EscapeSequence a -> Bool #

length :: EscapeSequence a -> Int #

elem :: Eq a => a -> EscapeSequence a -> Bool #

maximum :: Ord a => EscapeSequence a -> a #

minimum :: Ord a => EscapeSequence a -> a #

sum :: Num a => EscapeSequence a -> a #

product :: Num a => EscapeSequence a -> a #

Traversable EscapeSequence Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> EscapeSequence a -> f (EscapeSequence b) #

sequenceA :: Applicative f => EscapeSequence (f a) -> f (EscapeSequence a) #

mapM :: Monad m => (a -> m b) -> EscapeSequence a -> m (EscapeSequence b) #

sequence :: Monad m => EscapeSequence (m a) -> m (EscapeSequence a) #

SymbolMatching EscapeSequence Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal EscapeSequence Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (EscapeSequence a)

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 #

Generic1 EscapeSequence Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 EscapeSequence :: k -> Type #

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.5.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)))
type Rep1 EscapeSequence Source # 
Instance details

Defined in TreeSitter.Python.AST

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

data TypeConversion a Source #

Constructors

TypeConversion 

Fields

Instances
Functor TypeConversion Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> TypeConversion a -> TypeConversion b #

(<$) :: a -> TypeConversion b -> TypeConversion a #

Foldable TypeConversion Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => TypeConversion m -> m #

foldMap :: Monoid m => (a -> m) -> TypeConversion a -> m #

foldr :: (a -> b -> b) -> b -> TypeConversion a -> b #

foldr' :: (a -> b -> b) -> b -> TypeConversion a -> b #

foldl :: (b -> a -> b) -> b -> TypeConversion a -> b #

foldl' :: (b -> a -> b) -> b -> TypeConversion a -> b #

foldr1 :: (a -> a -> a) -> TypeConversion a -> a #

foldl1 :: (a -> a -> a) -> TypeConversion a -> a #

toList :: TypeConversion a -> [a] #

null :: TypeConversion a -> Bool #

length :: TypeConversion a -> Int #

elem :: Eq a => a -> TypeConversion a -> Bool #

maximum :: Ord a => TypeConversion a -> a #

minimum :: Ord a => TypeConversion a -> a #

sum :: Num a => TypeConversion a -> a #

product :: Num a => TypeConversion a -> a #

Traversable TypeConversion Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> TypeConversion a -> f (TypeConversion b) #

sequenceA :: Applicative f => TypeConversion (f a) -> f (TypeConversion a) #

mapM :: Monad m => (a -> m b) -> TypeConversion a -> m (TypeConversion b) #

sequence :: Monad m => TypeConversion (m a) -> m (TypeConversion a) #

SymbolMatching TypeConversion Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal TypeConversion Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (TypeConversion a)

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 #

Generic1 TypeConversion Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 TypeConversion :: k -> Type #

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.5.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)))
type Rep1 TypeConversion Source # 
Instance details

Defined in TreeSitter.Python.AST

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

data Integer a Source #

Constructors

Integer 

Fields

Instances
Functor Integer Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Integer a -> Integer b #

(<$) :: a -> Integer b -> Integer a #

Foldable Integer Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Integer m -> m #

foldMap :: Monoid m => (a -> m) -> Integer a -> m #

foldr :: (a -> b -> b) -> b -> Integer a -> b #

foldr' :: (a -> b -> b) -> b -> Integer a -> b #

foldl :: (b -> a -> b) -> b -> Integer a -> b #

foldl' :: (b -> a -> b) -> b -> Integer a -> b #

foldr1 :: (a -> a -> a) -> Integer a -> a #

foldl1 :: (a -> a -> a) -> Integer a -> a #

toList :: Integer a -> [a] #

null :: Integer a -> Bool #

length :: Integer a -> Int #

elem :: Eq a => a -> Integer a -> Bool #

maximum :: Ord a => Integer a -> a #

minimum :: Ord a => Integer a -> a #

sum :: Num a => Integer a -> a #

product :: Num a => Integer a -> a #

Traversable Integer Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Integer a -> f (Integer b) #

sequenceA :: Applicative f => Integer (f a) -> f (Integer a) #

mapM :: Monad m => (a -> m b) -> Integer a -> m (Integer b) #

sequence :: Monad m => Integer (m a) -> m (Integer a) #

SymbolMatching Integer Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Integer -> Node -> Bool

showFailure :: Proxy Integer -> Node -> String

Unmarshal Integer Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Integer a)

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 #

Generic1 Integer Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Integer :: k -> Type #

Methods

from1 :: Integer a -> Rep1 Integer a #

to1 :: Rep1 Integer a -> Integer a #

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.5.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)))
type Rep1 Integer Source # 
Instance details

Defined in TreeSitter.Python.AST

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

data Float a Source #

Constructors

Float 

Fields

Instances
Functor Float Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Float a -> Float b #

(<$) :: a -> Float b -> Float a #

Foldable Float Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Float m -> m #

foldMap :: Monoid m => (a -> m) -> Float a -> m #

foldr :: (a -> b -> b) -> b -> Float a -> b #

foldr' :: (a -> b -> b) -> b -> Float a -> b #

foldl :: (b -> a -> b) -> b -> Float a -> b #

foldl' :: (b -> a -> b) -> b -> Float a -> b #

foldr1 :: (a -> a -> a) -> Float a -> a #

foldl1 :: (a -> a -> a) -> Float a -> a #

toList :: Float a -> [a] #

null :: Float a -> Bool #

length :: Float a -> Int #

elem :: Eq a => a -> Float a -> Bool #

maximum :: Ord a => Float a -> a #

minimum :: Ord a => Float a -> a #

sum :: Num a => Float a -> a #

product :: Num a => Float a -> a #

Traversable Float Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Float a -> f (Float b) #

sequenceA :: Applicative f => Float (f a) -> f (Float a) #

mapM :: Monad m => (a -> m b) -> Float a -> m (Float b) #

sequence :: Monad m => Float (m a) -> m (Float a) #

SymbolMatching Float Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Float -> Node -> Bool

showFailure :: Proxy Float -> Node -> String

Unmarshal Float Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Float a)

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 #

Generic1 Float Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Float :: k -> Type #

Methods

from1 :: Float a -> Rep1 Float a #

to1 :: Rep1 Float a -> Float a #

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.5.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)))
type Rep1 Float Source # 
Instance details

Defined in TreeSitter.Python.AST

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

data Identifier a Source #

Constructors

Identifier 

Fields

Instances
Functor Identifier Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Identifier a -> Identifier b #

(<$) :: a -> Identifier b -> Identifier a #

Foldable Identifier Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Identifier m -> m #

foldMap :: Monoid m => (a -> m) -> Identifier a -> m #

foldr :: (a -> b -> b) -> b -> Identifier a -> b #

foldr' :: (a -> b -> b) -> b -> Identifier a -> b #

foldl :: (b -> a -> b) -> b -> Identifier a -> b #

foldl' :: (b -> a -> b) -> b -> Identifier a -> b #

foldr1 :: (a -> a -> a) -> Identifier a -> a #

foldl1 :: (a -> a -> a) -> Identifier a -> a #

toList :: Identifier a -> [a] #

null :: Identifier a -> Bool #

length :: Identifier a -> Int #

elem :: Eq a => a -> Identifier a -> Bool #

maximum :: Ord a => Identifier a -> a #

minimum :: Ord a => Identifier a -> a #

sum :: Num a => Identifier a -> a #

product :: Num a => Identifier a -> a #

Traversable Identifier Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Identifier a -> f (Identifier b) #

sequenceA :: Applicative f => Identifier (f a) -> f (Identifier a) #

mapM :: Monad m => (a -> m b) -> Identifier a -> m (Identifier b) #

sequence :: Monad m => Identifier (m a) -> m (Identifier a) #

SymbolMatching Identifier Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal Identifier Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Identifier a)

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 #

Generic1 Identifier Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Identifier :: k -> Type #

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.5.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)))
type Rep1 Identifier Source # 
Instance details

Defined in TreeSitter.Python.AST

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

data NonlocalStatement a Source #

Constructors

NonlocalStatement 

Fields

Instances
Functor NonlocalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable NonlocalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => NonlocalStatement m -> m #

foldMap :: Monoid m => (a -> m) -> NonlocalStatement a -> m #

foldr :: (a -> b -> b) -> b -> NonlocalStatement a -> b #

foldr' :: (a -> b -> b) -> b -> NonlocalStatement a -> b #

foldl :: (b -> a -> b) -> b -> NonlocalStatement a -> b #

foldl' :: (b -> a -> b) -> b -> NonlocalStatement a -> b #

foldr1 :: (a -> a -> a) -> NonlocalStatement a -> a #

foldl1 :: (a -> a -> a) -> NonlocalStatement a -> a #

toList :: NonlocalStatement a -> [a] #

null :: NonlocalStatement a -> Bool #

length :: NonlocalStatement a -> Int #

elem :: Eq a => a -> NonlocalStatement a -> Bool #

maximum :: Ord a => NonlocalStatement a -> a #

minimum :: Ord a => NonlocalStatement a -> a #

sum :: Num a => NonlocalStatement a -> a #

product :: Num a => NonlocalStatement a -> a #

Traversable NonlocalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> NonlocalStatement a -> f (NonlocalStatement b) #

sequenceA :: Applicative f => NonlocalStatement (f a) -> f (NonlocalStatement a) #

mapM :: Monad m => (a -> m b) -> NonlocalStatement a -> m (NonlocalStatement b) #

sequence :: Monad m => NonlocalStatement (m a) -> m (NonlocalStatement a) #

SymbolMatching NonlocalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal NonlocalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (NonlocalStatement a)

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 #

Generic1 NonlocalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 NonlocalStatement :: k -> Type #

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.5.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)))))
type Rep1 NonlocalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 NonlocalStatement = D1 (MetaData "NonlocalStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "NonlocalStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 Identifier)))

data GlobalStatement a Source #

Constructors

GlobalStatement 

Fields

Instances
Functor GlobalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> GlobalStatement a -> GlobalStatement b #

(<$) :: a -> GlobalStatement b -> GlobalStatement a #

Foldable GlobalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => GlobalStatement m -> m #

foldMap :: Monoid m => (a -> m) -> GlobalStatement a -> m #

foldr :: (a -> b -> b) -> b -> GlobalStatement a -> b #

foldr' :: (a -> b -> b) -> b -> GlobalStatement a -> b #

foldl :: (b -> a -> b) -> b -> GlobalStatement a -> b #

foldl' :: (b -> a -> b) -> b -> GlobalStatement a -> b #

foldr1 :: (a -> a -> a) -> GlobalStatement a -> a #

foldl1 :: (a -> a -> a) -> GlobalStatement a -> a #

toList :: GlobalStatement a -> [a] #

null :: GlobalStatement a -> Bool #

length :: GlobalStatement a -> Int #

elem :: Eq a => a -> GlobalStatement a -> Bool #

maximum :: Ord a => GlobalStatement a -> a #

minimum :: Ord a => GlobalStatement a -> a #

sum :: Num a => GlobalStatement a -> a #

product :: Num a => GlobalStatement a -> a #

Traversable GlobalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> GlobalStatement a -> f (GlobalStatement b) #

sequenceA :: Applicative f => GlobalStatement (f a) -> f (GlobalStatement a) #

mapM :: Monad m => (a -> m b) -> GlobalStatement a -> m (GlobalStatement b) #

sequence :: Monad m => GlobalStatement (m a) -> m (GlobalStatement a) #

SymbolMatching GlobalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal GlobalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (GlobalStatement a)

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 #

Generic1 GlobalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 GlobalStatement :: k -> Type #

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.5.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)))))
type Rep1 GlobalStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 GlobalStatement = D1 (MetaData "GlobalStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "GlobalStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 Identifier)))

data DottedName a Source #

Constructors

DottedName 

Fields

Instances
Functor DottedName Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> DottedName a -> DottedName b #

(<$) :: a -> DottedName b -> DottedName a #

Foldable DottedName Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => DottedName m -> m #

foldMap :: Monoid m => (a -> m) -> DottedName a -> m #

foldr :: (a -> b -> b) -> b -> DottedName a -> b #

foldr' :: (a -> b -> b) -> b -> DottedName a -> b #

foldl :: (b -> a -> b) -> b -> DottedName a -> b #

foldl' :: (b -> a -> b) -> b -> DottedName a -> b #

foldr1 :: (a -> a -> a) -> DottedName a -> a #

foldl1 :: (a -> a -> a) -> DottedName a -> a #

toList :: DottedName a -> [a] #

null :: DottedName a -> Bool #

length :: DottedName a -> Int #

elem :: Eq a => a -> DottedName a -> Bool #

maximum :: Ord a => DottedName a -> a #

minimum :: Ord a => DottedName a -> a #

sum :: Num a => DottedName a -> a #

product :: Num a => DottedName a -> a #

Traversable DottedName Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> DottedName a -> f (DottedName b) #

sequenceA :: Applicative f => DottedName (f a) -> f (DottedName a) #

mapM :: Monad m => (a -> m b) -> DottedName a -> m (DottedName b) #

sequence :: Monad m => DottedName (m a) -> m (DottedName a) #

SymbolMatching DottedName Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal DottedName Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (DottedName a)

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 #

Generic1 DottedName Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 DottedName :: k -> Type #

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.5.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)))))
type Rep1 DottedName Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 DottedName = D1 (MetaData "DottedName" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "DottedName" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 Identifier)))

data RelativeImport a Source #

Instances
Functor RelativeImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> RelativeImport a -> RelativeImport b #

(<$) :: a -> RelativeImport b -> RelativeImport a #

Foldable RelativeImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => RelativeImport m -> m #

foldMap :: Monoid m => (a -> m) -> RelativeImport a -> m #

foldr :: (a -> b -> b) -> b -> RelativeImport a -> b #

foldr' :: (a -> b -> b) -> b -> RelativeImport a -> b #

foldl :: (b -> a -> b) -> b -> RelativeImport a -> b #

foldl' :: (b -> a -> b) -> b -> RelativeImport a -> b #

foldr1 :: (a -> a -> a) -> RelativeImport a -> a #

foldl1 :: (a -> a -> a) -> RelativeImport a -> a #

toList :: RelativeImport a -> [a] #

null :: RelativeImport a -> Bool #

length :: RelativeImport a -> Int #

elem :: Eq a => a -> RelativeImport a -> Bool #

maximum :: Ord a => RelativeImport a -> a #

minimum :: Ord a => RelativeImport a -> a #

sum :: Num a => RelativeImport a -> a #

product :: Num a => RelativeImport a -> a #

Traversable RelativeImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> RelativeImport a -> f (RelativeImport b) #

sequenceA :: Applicative f => RelativeImport (f a) -> f (RelativeImport a) #

mapM :: Monad m => (a -> m b) -> RelativeImport a -> m (RelativeImport b) #

sequence :: Monad m => RelativeImport (m a) -> m (RelativeImport a) #

SymbolMatching RelativeImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal RelativeImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (RelativeImport a)

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 #

Generic1 RelativeImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 RelativeImport :: k -> Type #

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.5.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 ((DottedName :+: ImportPrefix) a)))))
type Rep1 RelativeImport Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 RelativeImport = D1 (MetaData "RelativeImport" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "RelativeImport" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 (DottedName :+: ImportPrefix))))

data AliasedImport a Source #

Constructors

AliasedImport 

Fields

Instances
Functor AliasedImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AliasedImport a -> AliasedImport b #

(<$) :: a -> AliasedImport b -> AliasedImport a #

Foldable AliasedImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AliasedImport m -> m #

foldMap :: Monoid m => (a -> m) -> AliasedImport a -> m #

foldr :: (a -> b -> b) -> b -> AliasedImport a -> b #

foldr' :: (a -> b -> b) -> b -> AliasedImport a -> b #

foldl :: (b -> a -> b) -> b -> AliasedImport a -> b #

foldl' :: (b -> a -> b) -> b -> AliasedImport a -> b #

foldr1 :: (a -> a -> a) -> AliasedImport a -> a #

foldl1 :: (a -> a -> a) -> AliasedImport a -> a #

toList :: AliasedImport a -> [a] #

null :: AliasedImport a -> Bool #

length :: AliasedImport a -> Int #

elem :: Eq a => a -> AliasedImport a -> Bool #

maximum :: Ord a => AliasedImport a -> a #

minimum :: Ord a => AliasedImport a -> a #

sum :: Num a => AliasedImport a -> a #

product :: Num a => AliasedImport a -> a #

Traversable AliasedImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AliasedImport a -> f (AliasedImport b) #

sequenceA :: Applicative f => AliasedImport (f a) -> f (AliasedImport a) #

mapM :: Monad m => (a -> m b) -> AliasedImport a -> m (AliasedImport b) #

sequence :: Monad m => AliasedImport (m a) -> m (AliasedImport a) #

SymbolMatching AliasedImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AliasedImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AliasedImport a)

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 #

Generic1 AliasedImport Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AliasedImport :: k -> Type #

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.5.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)))))
type Rep1 AliasedImport Source # 
Instance details

Defined in TreeSitter.Python.AST

data ImportStatement a Source #

Constructors

ImportStatement 

Fields

Instances
Functor ImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> ImportStatement a -> ImportStatement b #

(<$) :: a -> ImportStatement b -> ImportStatement a #

Foldable ImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ImportStatement m -> m #

foldMap :: Monoid m => (a -> m) -> ImportStatement a -> m #

foldr :: (a -> b -> b) -> b -> ImportStatement a -> b #

foldr' :: (a -> b -> b) -> b -> ImportStatement a -> b #

foldl :: (b -> a -> b) -> b -> ImportStatement a -> b #

foldl' :: (b -> a -> b) -> b -> ImportStatement a -> b #

foldr1 :: (a -> a -> a) -> ImportStatement a -> a #

foldl1 :: (a -> a -> a) -> ImportStatement a -> a #

toList :: ImportStatement a -> [a] #

null :: ImportStatement a -> Bool #

length :: ImportStatement a -> Int #

elem :: Eq a => a -> ImportStatement a -> Bool #

maximum :: Ord a => ImportStatement a -> a #

minimum :: Ord a => ImportStatement a -> a #

sum :: Num a => ImportStatement a -> a #

product :: Num a => ImportStatement a -> a #

Traversable ImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ImportStatement a -> f (ImportStatement b) #

sequenceA :: Applicative f => ImportStatement (f a) -> f (ImportStatement a) #

mapM :: Monad m => (a -> m b) -> ImportStatement a -> m (ImportStatement b) #

sequence :: Monad m => ImportStatement (m a) -> m (ImportStatement a) #

SymbolMatching ImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ImportStatement a)

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 #

Generic1 ImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ImportStatement :: k -> Type #

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.5.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 [(AliasedImport :+: DottedName) a])))
type Rep1 ImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ImportStatement = D1 (MetaData "ImportStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ImportStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 (AliasedImport :+: DottedName))))

data ImportFromStatement a Source #

Instances
Functor ImportFromStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable ImportFromStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ImportFromStatement m -> m #

foldMap :: Monoid m => (a -> m) -> ImportFromStatement a -> m #

foldr :: (a -> b -> b) -> b -> ImportFromStatement a -> b #

foldr' :: (a -> b -> b) -> b -> ImportFromStatement a -> b #

foldl :: (b -> a -> b) -> b -> ImportFromStatement a -> b #

foldl' :: (b -> a -> b) -> b -> ImportFromStatement a -> b #

foldr1 :: (a -> a -> a) -> ImportFromStatement a -> a #

foldl1 :: (a -> a -> a) -> ImportFromStatement a -> a #

toList :: ImportFromStatement a -> [a] #

null :: ImportFromStatement a -> Bool #

length :: ImportFromStatement a -> Int #

elem :: Eq a => a -> ImportFromStatement a -> Bool #

maximum :: Ord a => ImportFromStatement a -> a #

minimum :: Ord a => ImportFromStatement a -> a #

sum :: Num a => ImportFromStatement a -> a #

product :: Num a => ImportFromStatement a -> a #

Traversable ImportFromStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching ImportFromStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ImportFromStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ImportFromStatement a)

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 #

Generic1 ImportFromStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ImportFromStatement :: k -> Type #

type Rep (ImportFromStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ImportFromStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

data FutureImportStatement a Source #

Constructors

FutureImportStatement 

Fields

Instances
Functor FutureImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable FutureImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => FutureImportStatement m -> m #

foldMap :: Monoid m => (a -> m) -> FutureImportStatement a -> m #

foldr :: (a -> b -> b) -> b -> FutureImportStatement a -> b #

foldr' :: (a -> b -> b) -> b -> FutureImportStatement a -> b #

foldl :: (b -> a -> b) -> b -> FutureImportStatement a -> b #

foldl' :: (b -> a -> b) -> b -> FutureImportStatement a -> b #

foldr1 :: (a -> a -> a) -> FutureImportStatement a -> a #

foldl1 :: (a -> a -> a) -> FutureImportStatement a -> a #

toList :: FutureImportStatement a -> [a] #

null :: FutureImportStatement a -> Bool #

length :: FutureImportStatement a -> Int #

elem :: Eq a => a -> FutureImportStatement a -> Bool #

maximum :: Ord a => FutureImportStatement a -> a #

minimum :: Ord a => FutureImportStatement a -> a #

sum :: Num a => FutureImportStatement a -> a #

product :: Num a => FutureImportStatement a -> a #

Traversable FutureImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching FutureImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal FutureImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (FutureImportStatement a)

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 #

Generic1 FutureImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 FutureImportStatement :: k -> Type #

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.5.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 [(AliasedImport :+: DottedName) a])))
type Rep1 FutureImportStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 FutureImportStatement = D1 (MetaData "FutureImportStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "FutureImportStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 (AliasedImport :+: DottedName))))

data True a Source #

Constructors

True 

Fields

Instances
Functor True Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> True a -> True b #

(<$) :: a -> True b -> True a #

Foldable True Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => True m -> m #

foldMap :: Monoid m => (a -> m) -> True a -> m #

foldr :: (a -> b -> b) -> b -> True a -> b #

foldr' :: (a -> b -> b) -> b -> True a -> b #

foldl :: (b -> a -> b) -> b -> True a -> b #

foldl' :: (b -> a -> b) -> b -> True a -> b #

foldr1 :: (a -> a -> a) -> True a -> a #

foldl1 :: (a -> a -> a) -> True a -> a #

toList :: True a -> [a] #

null :: True a -> Bool #

length :: True a -> Int #

elem :: Eq a => a -> True a -> Bool #

maximum :: Ord a => True a -> a #

minimum :: Ord a => True a -> a #

sum :: Num a => True a -> a #

product :: Num a => True a -> a #

Traversable True Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> True a -> f (True b) #

sequenceA :: Applicative f => True (f a) -> f (True a) #

mapM :: Monad m => (a -> m b) -> True a -> m (True b) #

sequence :: Monad m => True (m a) -> m (True a) #

SymbolMatching True Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy True -> Node -> Bool

showFailure :: Proxy True -> Node -> String

Unmarshal True Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (True a)

Eq a => Eq (True a) Source # 
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 #

Generic1 True Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 True :: k -> Type #

Methods

from1 :: True a -> Rep1 True a #

to1 :: Rep1 True a -> True a #

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.5.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)))
type Rep1 True Source # 
Instance details

Defined in TreeSitter.Python.AST

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

data False a Source #

Constructors

False 

Fields

Instances
Functor False Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> False a -> False b #

(<$) :: a -> False b -> False a #

Foldable False Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => False m -> m #

foldMap :: Monoid m => (a -> m) -> False a -> m #

foldr :: (a -> b -> b) -> b -> False a -> b #

foldr' :: (a -> b -> b) -> b -> False a -> b #

foldl :: (b -> a -> b) -> b -> False a -> b #

foldl' :: (b -> a -> b) -> b -> False a -> b #

foldr1 :: (a -> a -> a) -> False a -> a #

foldl1 :: (a -> a -> a) -> False a -> a #

toList :: False a -> [a] #

null :: False a -> Bool #

length :: False a -> Int #

elem :: Eq a => a -> False a -> Bool #

maximum :: Ord a => False a -> a #

minimum :: Ord a => False a -> a #

sum :: Num a => False a -> a #

product :: Num a => False a -> a #

Traversable False Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> False a -> f (False b) #

sequenceA :: Applicative f => False (f a) -> f (False a) #

mapM :: Monad m => (a -> m b) -> False a -> m (False b) #

sequence :: Monad m => False (m a) -> m (False a) #

SymbolMatching False Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy False -> Node -> Bool

showFailure :: Proxy False -> Node -> String

Unmarshal False Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (False a)

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 #

Generic1 False Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 False :: k -> Type #

Methods

from1 :: False a -> Rep1 False a #

to1 :: Rep1 False a -> False a #

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.5.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)))
type Rep1 False Source # 
Instance details

Defined in TreeSitter.Python.AST

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

data None a Source #

Constructors

None 

Fields

Instances
Functor None Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> None a -> None b #

(<$) :: a -> None b -> None a #

Foldable None Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => None m -> m #

foldMap :: Monoid m => (a -> m) -> None a -> m #

foldr :: (a -> b -> b) -> b -> None a -> b #

foldr' :: (a -> b -> b) -> b -> None a -> b #

foldl :: (b -> a -> b) -> b -> None a -> b #

foldl' :: (b -> a -> b) -> b -> None a -> b #

foldr1 :: (a -> a -> a) -> None a -> a #

foldl1 :: (a -> a -> a) -> None a -> a #

toList :: None a -> [a] #

null :: None a -> Bool #

length :: None a -> Int #

elem :: Eq a => a -> None a -> Bool #

maximum :: Ord a => None a -> a #

minimum :: Ord a => None a -> a #

sum :: Num a => None a -> a #

product :: Num a => None a -> a #

Traversable None Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> None a -> f (None b) #

sequenceA :: Applicative f => None (f a) -> f (None a) #

mapM :: Monad m => (a -> m b) -> None a -> m (None b) #

sequence :: Monad m => None (m a) -> m (None a) #

SymbolMatching None Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy None -> Node -> Bool

showFailure :: Proxy None -> Node -> String

Unmarshal None Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (None a)

Eq a => Eq (None a) Source # 
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 #

Generic1 None Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 None :: k -> Type #

Methods

from1 :: None a -> Rep1 None a #

to1 :: Rep1 None a -> None a #

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.5.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)))
type Rep1 None Source # 
Instance details

Defined in TreeSitter.Python.AST

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

data PrimaryExpression a Source #

Instances
Functor PrimaryExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable PrimaryExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => PrimaryExpression m -> m #

foldMap :: Monoid m => (a -> m) -> PrimaryExpression a -> m #

foldr :: (a -> b -> b) -> b -> PrimaryExpression a -> b #

foldr' :: (a -> b -> b) -> b -> PrimaryExpression a -> b #

foldl :: (b -> a -> b) -> b -> PrimaryExpression a -> b #

foldl' :: (b -> a -> b) -> b -> PrimaryExpression a -> b #

foldr1 :: (a -> a -> a) -> PrimaryExpression a -> a #

foldl1 :: (a -> a -> a) -> PrimaryExpression a -> a #

toList :: PrimaryExpression a -> [a] #

null :: PrimaryExpression a -> Bool #

length :: PrimaryExpression a -> Int #

elem :: Eq a => a -> PrimaryExpression a -> Bool #

maximum :: Ord a => PrimaryExpression a -> a #

minimum :: Ord a => PrimaryExpression a -> a #

sum :: Num a => PrimaryExpression a -> a #

product :: Num a => PrimaryExpression a -> a #

Traversable PrimaryExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> PrimaryExpression a -> f (PrimaryExpression b) #

sequenceA :: Applicative f => PrimaryExpression (f a) -> f (PrimaryExpression a) #

mapM :: Monad m => (a -> m b) -> PrimaryExpression a -> m (PrimaryExpression b) #

sequence :: Monad m => PrimaryExpression (m a) -> m (PrimaryExpression a) #

SymbolMatching PrimaryExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal PrimaryExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (PrimaryExpression a)

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 #

Generic1 PrimaryExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 PrimaryExpression :: k -> Type #

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.5.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))))))))
type Rep1 PrimaryExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 PrimaryExpression = D1 (MetaData "PrimaryExpression" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) ((((C1 (MetaCons "AttributePrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Attribute)) :+: C1 (MetaCons "BinaryOperatorPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 BinaryOperator))) :+: (C1 (MetaCons "CallPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Call)) :+: (C1 (MetaCons "ConcatenatedStringPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ConcatenatedString)) :+: C1 (MetaCons "DictionaryPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Dictionary))))) :+: ((C1 (MetaCons "DictionaryComprehensionPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 DictionaryComprehension)) :+: (C1 (MetaCons "EllipsisPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Ellipsis)) :+: C1 (MetaCons "FalsePrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 False)))) :+: (C1 (MetaCons "FloatPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Float)) :+: (C1 (MetaCons "GeneratorExpressionPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 GeneratorExpression)) :+: C1 (MetaCons "IdentifierPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Identifier)))))) :+: (((C1 (MetaCons "IntegerPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Integer)) :+: (C1 (MetaCons "ListPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 List)) :+: C1 (MetaCons "ListComprehensionPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ListComprehension)))) :+: (C1 (MetaCons "NonePrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 None)) :+: (C1 (MetaCons "ParenthesizedExpressionPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ParenthesizedExpression)) :+: C1 (MetaCons "SetPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Set))))) :+: ((C1 (MetaCons "SetComprehensionPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 SetComprehension)) :+: (C1 (MetaCons "StringPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 String)) :+: C1 (MetaCons "SubscriptPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Subscript)))) :+: (C1 (MetaCons "TruePrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 True)) :+: (C1 (MetaCons "TuplePrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Tuple)) :+: C1 (MetaCons "UnaryOperatorPrimaryExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 UnaryOperator)))))))

data UnaryOperator a Source #

Instances
Functor UnaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> UnaryOperator a -> UnaryOperator b #

(<$) :: a -> UnaryOperator b -> UnaryOperator a #

Foldable UnaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => UnaryOperator m -> m #

foldMap :: Monoid m => (a -> m) -> UnaryOperator a -> m #

foldr :: (a -> b -> b) -> b -> UnaryOperator a -> b #

foldr' :: (a -> b -> b) -> b -> UnaryOperator a -> b #

foldl :: (b -> a -> b) -> b -> UnaryOperator a -> b #

foldl' :: (b -> a -> b) -> b -> UnaryOperator a -> b #

foldr1 :: (a -> a -> a) -> UnaryOperator a -> a #

foldl1 :: (a -> a -> a) -> UnaryOperator a -> a #

toList :: UnaryOperator a -> [a] #

null :: UnaryOperator a -> Bool #

length :: UnaryOperator a -> Int #

elem :: Eq a => a -> UnaryOperator a -> Bool #

maximum :: Ord a => UnaryOperator a -> a #

minimum :: Ord a => UnaryOperator a -> a #

sum :: Num a => UnaryOperator a -> a #

product :: Num a => UnaryOperator a -> a #

Traversable UnaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> UnaryOperator a -> f (UnaryOperator b) #

sequenceA :: Applicative f => UnaryOperator (f a) -> f (UnaryOperator a) #

mapM :: Monad m => (a -> m b) -> UnaryOperator a -> m (UnaryOperator b) #

sequence :: Monad m => UnaryOperator (m a) -> m (UnaryOperator a) #

SymbolMatching UnaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal UnaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (UnaryOperator a)

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 #

Generic1 UnaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 UnaryOperator :: k -> Type #

type Rep (UnaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 UnaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

data Tuple a Source #

Constructors

Tuple 

Fields

Instances
Functor Tuple Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Tuple a -> Tuple b #

(<$) :: a -> Tuple b -> Tuple a #

Foldable Tuple Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Tuple m -> m #

foldMap :: Monoid m => (a -> m) -> Tuple a -> m #

foldr :: (a -> b -> b) -> b -> Tuple a -> b #

foldr' :: (a -> b -> b) -> b -> Tuple a -> b #

foldl :: (b -> a -> b) -> b -> Tuple a -> b #

foldl' :: (b -> a -> b) -> b -> Tuple a -> b #

foldr1 :: (a -> a -> a) -> Tuple a -> a #

foldl1 :: (a -> a -> a) -> Tuple a -> a #

toList :: Tuple a -> [a] #

null :: Tuple a -> Bool #

length :: Tuple a -> Int #

elem :: Eq a => a -> Tuple a -> Bool #

maximum :: Ord a => Tuple a -> a #

minimum :: Ord a => Tuple a -> a #

sum :: Num a => Tuple a -> a #

product :: Num a => Tuple a -> a #

Traversable Tuple Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Tuple a -> f (Tuple b) #

sequenceA :: Applicative f => Tuple (f a) -> f (Tuple a) #

mapM :: Monad m => (a -> m b) -> Tuple a -> m (Tuple b) #

sequence :: Monad m => Tuple (m a) -> m (Tuple a) #

SymbolMatching Tuple Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Tuple -> Node -> Bool

showFailure :: Proxy Tuple -> Node -> String

Unmarshal Tuple Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Tuple a)

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 #

Generic1 Tuple Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Tuple :: k -> Type #

Methods

from1 :: Tuple a -> Rep1 Tuple a #

to1 :: Rep1 Tuple a -> Tuple a #

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.5.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 [(Expression :+: Yield) a])))
type Rep1 Tuple Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Tuple = D1 (MetaData "Tuple" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Tuple" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 (Expression :+: Yield))))

data Yield a Source #

Constructors

Yield 
Instances
Functor Yield Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Yield a -> Yield b #

(<$) :: a -> Yield b -> Yield a #

Foldable Yield Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Yield m -> m #

foldMap :: Monoid m => (a -> m) -> Yield a -> m #

foldr :: (a -> b -> b) -> b -> Yield a -> b #

foldr' :: (a -> b -> b) -> b -> Yield a -> b #

foldl :: (b -> a -> b) -> b -> Yield a -> b #

foldl' :: (b -> a -> b) -> b -> Yield a -> b #

foldr1 :: (a -> a -> a) -> Yield a -> a #

foldl1 :: (a -> a -> a) -> Yield a -> a #

toList :: Yield a -> [a] #

null :: Yield a -> Bool #

length :: Yield a -> Int #

elem :: Eq a => a -> Yield a -> Bool #

maximum :: Ord a => Yield a -> a #

minimum :: Ord a => Yield a -> a #

sum :: Num a => Yield a -> a #

product :: Num a => Yield a -> a #

Traversable Yield Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Yield a -> f (Yield b) #

sequenceA :: Applicative f => Yield (f a) -> f (Yield a) #

mapM :: Monad m => (a -> m b) -> Yield a -> m (Yield b) #

sequence :: Monad m => Yield (m a) -> m (Yield a) #

SymbolMatching Yield Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Yield -> Node -> Bool

showFailure :: Proxy Yield -> Node -> String

Unmarshal Yield Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Yield a)

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 #

Generic1 Yield Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Yield :: k -> Type #

Methods

from1 :: Yield a -> Rep1 Yield a #

to1 :: Rep1 Yield a -> Yield a #

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.5.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 ((Expression :+: ExpressionList) a)))))
type Rep1 Yield Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Yield = D1 (MetaData "Yield" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Yield" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Maybe :.: Rec1 (Expression :+: ExpressionList))))

data ExpressionList a Source #

Constructors

ExpressionList 

Fields

Instances
Functor ExpressionList Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> ExpressionList a -> ExpressionList b #

(<$) :: a -> ExpressionList b -> ExpressionList a #

Foldable ExpressionList Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ExpressionList m -> m #

foldMap :: Monoid m => (a -> m) -> ExpressionList a -> m #

foldr :: (a -> b -> b) -> b -> ExpressionList a -> b #

foldr' :: (a -> b -> b) -> b -> ExpressionList a -> b #

foldl :: (b -> a -> b) -> b -> ExpressionList a -> b #

foldl' :: (b -> a -> b) -> b -> ExpressionList a -> b #

foldr1 :: (a -> a -> a) -> ExpressionList a -> a #

foldl1 :: (a -> a -> a) -> ExpressionList a -> a #

toList :: ExpressionList a -> [a] #

null :: ExpressionList a -> Bool #

length :: ExpressionList a -> Int #

elem :: Eq a => a -> ExpressionList a -> Bool #

maximum :: Ord a => ExpressionList a -> a #

minimum :: Ord a => ExpressionList a -> a #

sum :: Num a => ExpressionList a -> a #

product :: Num a => ExpressionList a -> a #

Traversable ExpressionList Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ExpressionList a -> f (ExpressionList b) #

sequenceA :: Applicative f => ExpressionList (f a) -> f (ExpressionList a) #

mapM :: Monad m => (a -> m b) -> ExpressionList a -> m (ExpressionList b) #

sequence :: Monad m => ExpressionList (m a) -> m (ExpressionList a) #

SymbolMatching ExpressionList Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ExpressionList Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ExpressionList a)

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 #

Generic1 ExpressionList Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ExpressionList :: k -> Type #

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.5.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)))))
type Rep1 ExpressionList Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ExpressionList = D1 (MetaData "ExpressionList" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ExpressionList" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 Expression)))

data Expression a Source #

Instances
Functor Expression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Expression a -> Expression b #

(<$) :: a -> Expression b -> Expression a #

Foldable Expression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Expression m -> m #

foldMap :: Monoid m => (a -> m) -> Expression a -> m #

foldr :: (a -> b -> b) -> b -> Expression a -> b #

foldr' :: (a -> b -> b) -> b -> Expression a -> b #

foldl :: (b -> a -> b) -> b -> Expression a -> b #

foldl' :: (b -> a -> b) -> b -> Expression a -> b #

foldr1 :: (a -> a -> a) -> Expression a -> a #

foldl1 :: (a -> a -> a) -> Expression a -> a #

toList :: Expression a -> [a] #

null :: Expression a -> Bool #

length :: Expression a -> Int #

elem :: Eq a => a -> Expression a -> Bool #

maximum :: Ord a => Expression a -> a #

minimum :: Ord a => Expression a -> a #

sum :: Num a => Expression a -> a #

product :: Num a => Expression a -> a #

Traversable Expression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Expression a -> f (Expression b) #

sequenceA :: Applicative f => Expression (f a) -> f (Expression a) #

mapM :: Monad m => (a -> m b) -> Expression a -> m (Expression b) #

sequence :: Monad m => Expression (m a) -> m (Expression a) #

SymbolMatching Expression Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal Expression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Expression a)

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 #

Generic1 Expression Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Expression :: k -> Type #

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.5.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))))))
type Rep1 Expression Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Expression = D1 (MetaData "Expression" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (((C1 (MetaCons "PrimaryExpressionExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 PrimaryExpression)) :+: C1 (MetaCons "AwaitExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Await))) :+: (C1 (MetaCons "BooleanOperatorExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 BooleanOperator)) :+: C1 (MetaCons "ComparisonOperatorExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ComparisonOperator)))) :+: ((C1 (MetaCons "ConditionalExpressionExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ConditionalExpression)) :+: C1 (MetaCons "LambdaExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Lambda))) :+: (C1 (MetaCons "NamedExpressionExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 NamedExpression)) :+: C1 (MetaCons "NotOperatorExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 NotOperator)))))

data NotOperator a Source #

Constructors

NotOperator 

Fields

Instances
Functor NotOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> NotOperator a -> NotOperator b #

(<$) :: a -> NotOperator b -> NotOperator a #

Foldable NotOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => NotOperator m -> m #

foldMap :: Monoid m => (a -> m) -> NotOperator a -> m #

foldr :: (a -> b -> b) -> b -> NotOperator a -> b #

foldr' :: (a -> b -> b) -> b -> NotOperator a -> b #

foldl :: (b -> a -> b) -> b -> NotOperator a -> b #

foldl' :: (b -> a -> b) -> b -> NotOperator a -> b #

foldr1 :: (a -> a -> a) -> NotOperator a -> a #

foldl1 :: (a -> a -> a) -> NotOperator a -> a #

toList :: NotOperator a -> [a] #

null :: NotOperator a -> Bool #

length :: NotOperator a -> Int #

elem :: Eq a => a -> NotOperator a -> Bool #

maximum :: Ord a => NotOperator a -> a #

minimum :: Ord a => NotOperator a -> a #

sum :: Num a => NotOperator a -> a #

product :: Num a => NotOperator a -> a #

Traversable NotOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> NotOperator a -> f (NotOperator b) #

sequenceA :: Applicative f => NotOperator (f a) -> f (NotOperator a) #

mapM :: Monad m => (a -> m b) -> NotOperator a -> m (NotOperator b) #

sequence :: Monad m => NotOperator (m a) -> m (NotOperator a) #

SymbolMatching NotOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal NotOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (NotOperator a)

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 #

Generic1 NotOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 NotOperator :: k -> Type #

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.5.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))))
type Rep1 NotOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 NotOperator = D1 (MetaData "NotOperator" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "NotOperator" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "argument") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Expression)))

data NamedExpression a Source #

Constructors

NamedExpression 

Fields

Instances
Functor NamedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> NamedExpression a -> NamedExpression b #

(<$) :: a -> NamedExpression b -> NamedExpression a #

Foldable NamedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => NamedExpression m -> m #

foldMap :: Monoid m => (a -> m) -> NamedExpression a -> m #

foldr :: (a -> b -> b) -> b -> NamedExpression a -> b #

foldr' :: (a -> b -> b) -> b -> NamedExpression a -> b #

foldl :: (b -> a -> b) -> b -> NamedExpression a -> b #

foldl' :: (b -> a -> b) -> b -> NamedExpression a -> b #

foldr1 :: (a -> a -> a) -> NamedExpression a -> a #

foldl1 :: (a -> a -> a) -> NamedExpression a -> a #

toList :: NamedExpression a -> [a] #

null :: NamedExpression a -> Bool #

length :: NamedExpression a -> Int #

elem :: Eq a => a -> NamedExpression a -> Bool #

maximum :: Ord a => NamedExpression a -> a #

minimum :: Ord a => NamedExpression a -> a #

sum :: Num a => NamedExpression a -> a #

product :: Num a => NamedExpression a -> a #

Traversable NamedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> NamedExpression a -> f (NamedExpression b) #

sequenceA :: Applicative f => NamedExpression (f a) -> f (NamedExpression a) #

mapM :: Monad m => (a -> m b) -> NamedExpression a -> m (NamedExpression b) #

sequence :: Monad m => NamedExpression (m a) -> m (NamedExpression a) #

SymbolMatching NamedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal NamedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (NamedExpression a)

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 #

Generic1 NamedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 NamedExpression :: k -> Type #

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.5.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)))))
type Rep1 NamedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

data Lambda a Source #

Constructors

Lambda 
Instances
Functor Lambda Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Lambda a -> Lambda b #

(<$) :: a -> Lambda b -> Lambda a #

Foldable Lambda Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Lambda m -> m #

foldMap :: Monoid m => (a -> m) -> Lambda a -> m #

foldr :: (a -> b -> b) -> b -> Lambda a -> b #

foldr' :: (a -> b -> b) -> b -> Lambda a -> b #

foldl :: (b -> a -> b) -> b -> Lambda a -> b #

foldl' :: (b -> a -> b) -> b -> Lambda a -> b #

foldr1 :: (a -> a -> a) -> Lambda a -> a #

foldl1 :: (a -> a -> a) -> Lambda a -> a #

toList :: Lambda a -> [a] #

null :: Lambda a -> Bool #

length :: Lambda a -> Int #

elem :: Eq a => a -> Lambda a -> Bool #

maximum :: Ord a => Lambda a -> a #

minimum :: Ord a => Lambda a -> a #

sum :: Num a => Lambda a -> a #

product :: Num a => Lambda a -> a #

Traversable Lambda Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Lambda a -> f (Lambda b) #

sequenceA :: Applicative f => Lambda (f a) -> f (Lambda a) #

mapM :: Monad m => (a -> m b) -> Lambda a -> m (Lambda b) #

sequence :: Monad m => Lambda (m a) -> m (Lambda a) #

SymbolMatching Lambda Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Lambda -> Node -> Bool

showFailure :: Proxy Lambda -> Node -> String

Unmarshal Lambda Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Lambda a)

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 #

Generic1 Lambda Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Lambda :: k -> Type #

Methods

from1 :: Lambda a -> Rep1 Lambda a #

to1 :: Rep1 Lambda a -> Lambda a #

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.5.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 ((Expression :+: Lambda) a)) :*: S1 (MetaSel (Just "parameters") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (LambdaParameters a))))))
type Rep1 Lambda Source # 
Instance details

Defined in TreeSitter.Python.AST

data LambdaParameters a Source #

Constructors

LambdaParameters 

Fields

Instances
Functor LambdaParameters Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> LambdaParameters a -> LambdaParameters b #

(<$) :: a -> LambdaParameters b -> LambdaParameters a #

Foldable LambdaParameters Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => LambdaParameters m -> m #

foldMap :: Monoid m => (a -> m) -> LambdaParameters a -> m #

foldr :: (a -> b -> b) -> b -> LambdaParameters a -> b #

foldr' :: (a -> b -> b) -> b -> LambdaParameters a -> b #

foldl :: (b -> a -> b) -> b -> LambdaParameters a -> b #

foldl' :: (b -> a -> b) -> b -> LambdaParameters a -> b #

foldr1 :: (a -> a -> a) -> LambdaParameters a -> a #

foldl1 :: (a -> a -> a) -> LambdaParameters a -> a #

toList :: LambdaParameters a -> [a] #

null :: LambdaParameters a -> Bool #

length :: LambdaParameters a -> Int #

elem :: Eq a => a -> LambdaParameters a -> Bool #

maximum :: Ord a => LambdaParameters a -> a #

minimum :: Ord a => LambdaParameters a -> a #

sum :: Num a => LambdaParameters a -> a #

product :: Num a => LambdaParameters a -> a #

Traversable LambdaParameters Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> LambdaParameters a -> f (LambdaParameters b) #

sequenceA :: Applicative f => LambdaParameters (f a) -> f (LambdaParameters a) #

mapM :: Monad m => (a -> m b) -> LambdaParameters a -> m (LambdaParameters b) #

sequence :: Monad m => LambdaParameters (m a) -> m (LambdaParameters a) #

SymbolMatching LambdaParameters Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal LambdaParameters Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (LambdaParameters a)

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 #

Generic1 LambdaParameters Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 LambdaParameters :: k -> Type #

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.5.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)))))
type Rep1 LambdaParameters Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 LambdaParameters = D1 (MetaData "LambdaParameters" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "LambdaParameters" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 Parameter)))

data Parameter a Source #

Instances
Functor Parameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Parameter a -> Parameter b #

(<$) :: a -> Parameter b -> Parameter a #

Foldable Parameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Parameter m -> m #

foldMap :: Monoid m => (a -> m) -> Parameter a -> m #

foldr :: (a -> b -> b) -> b -> Parameter a -> b #

foldr' :: (a -> b -> b) -> b -> Parameter a -> b #

foldl :: (b -> a -> b) -> b -> Parameter a -> b #

foldl' :: (b -> a -> b) -> b -> Parameter a -> b #

foldr1 :: (a -> a -> a) -> Parameter a -> a #

foldl1 :: (a -> a -> a) -> Parameter a -> a #

toList :: Parameter a -> [a] #

null :: Parameter a -> Bool #

length :: Parameter a -> Int #

elem :: Eq a => a -> Parameter a -> Bool #

maximum :: Ord a => Parameter a -> a #

minimum :: Ord a => Parameter a -> a #

sum :: Num a => Parameter a -> a #

product :: Num a => Parameter a -> a #

Traversable Parameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Parameter a -> f (Parameter b) #

sequenceA :: Applicative f => Parameter (f a) -> f (Parameter a) #

mapM :: Monad m => (a -> m b) -> Parameter a -> m (Parameter b) #

sequence :: Monad m => Parameter (m a) -> m (Parameter a) #

SymbolMatching Parameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Parameter -> Node -> Bool

showFailure :: Proxy Parameter -> Node -> String

Unmarshal Parameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Parameter a)

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 #

Generic1 Parameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Parameter :: k -> Type #

type Rep (Parameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Parameter Source # 
Instance details

Defined in TreeSitter.Python.AST

data TypedParameter a Source #

Instances
Functor TypedParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> TypedParameter a -> TypedParameter b #

(<$) :: a -> TypedParameter b -> TypedParameter a #

Foldable TypedParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => TypedParameter m -> m #

foldMap :: Monoid m => (a -> m) -> TypedParameter a -> m #

foldr :: (a -> b -> b) -> b -> TypedParameter a -> b #

foldr' :: (a -> b -> b) -> b -> TypedParameter a -> b #

foldl :: (b -> a -> b) -> b -> TypedParameter a -> b #

foldl' :: (b -> a -> b) -> b -> TypedParameter a -> b #

foldr1 :: (a -> a -> a) -> TypedParameter a -> a #

foldl1 :: (a -> a -> a) -> TypedParameter a -> a #

toList :: TypedParameter a -> [a] #

null :: TypedParameter a -> Bool #

length :: TypedParameter a -> Int #

elem :: Eq a => a -> TypedParameter a -> Bool #

maximum :: Ord a => TypedParameter a -> a #

minimum :: Ord a => TypedParameter a -> a #

sum :: Num a => TypedParameter a -> a #

product :: Num a => TypedParameter a -> a #

Traversable TypedParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> TypedParameter a -> f (TypedParameter b) #

sequenceA :: Applicative f => TypedParameter (f a) -> f (TypedParameter a) #

mapM :: Monad m => (a -> m b) -> TypedParameter a -> m (TypedParameter b) #

sequence :: Monad m => TypedParameter (m a) -> m (TypedParameter a) #

SymbolMatching TypedParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal TypedParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (TypedParameter a)

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 #

Generic1 TypedParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 TypedParameter :: k -> Type #

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.5.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 ((DictionarySplat :+: (Identifier :+: ListSplat)) a)))))
type Rep1 TypedParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

data Type a Source #

Constructors

Type 

Fields

Instances
Functor Type Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Type a -> Type b #

(<$) :: a -> Type b -> Type a #

Foldable Type Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Type m -> m #

foldMap :: Monoid m => (a -> m) -> Type a -> m #

foldr :: (a -> b -> b) -> b -> Type a -> b #

foldr' :: (a -> b -> b) -> b -> Type a -> b #

foldl :: (b -> a -> b) -> b -> Type a -> b #

foldl' :: (b -> a -> b) -> b -> Type a -> b #

foldr1 :: (a -> a -> a) -> Type a -> a #

foldl1 :: (a -> a -> a) -> Type a -> a #

toList :: Type a -> [a] #

null :: Type a -> Bool #

length :: Type a -> Int #

elem :: Eq a => a -> Type a -> Bool #

maximum :: Ord a => Type a -> a #

minimum :: Ord a => Type a -> a #

sum :: Num a => Type a -> a #

product :: Num a => Type a -> a #

Traversable Type Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Type a -> f (Type b) #

sequenceA :: Applicative f => Type (f a) -> f (Type a) #

mapM :: Monad m => (a -> m b) -> Type a -> m (Type b) #

sequence :: Monad m => Type (m a) -> m (Type a) #

SymbolMatching Type Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Type -> Node -> Bool

showFailure :: Proxy Type -> Node -> String

Unmarshal Type Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Type a)

Eq a => Eq (Type a) Source # 
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 #

Generic1 Type Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Type :: k -> Type #

Methods

from1 :: Type a -> Rep1 Type a #

to1 :: Rep1 Type a -> Type a #

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.5.0.0-inplace" False) (C1 (MetaCons "Type" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a))))
type Rep1 Type Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Type = D1 (MetaData "Type" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Type" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Expression)))

data ListSplat a Source #

Constructors

ListSplat 

Fields

Instances
Functor ListSplat Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> ListSplat a -> ListSplat b #

(<$) :: a -> ListSplat b -> ListSplat a #

Foldable ListSplat Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ListSplat m -> m #

foldMap :: Monoid m => (a -> m) -> ListSplat a -> m #

foldr :: (a -> b -> b) -> b -> ListSplat a -> b #

foldr' :: (a -> b -> b) -> b -> ListSplat a -> b #

foldl :: (b -> a -> b) -> b -> ListSplat a -> b #

foldl' :: (b -> a -> b) -> b -> ListSplat a -> b #

foldr1 :: (a -> a -> a) -> ListSplat a -> a #

foldl1 :: (a -> a -> a) -> ListSplat a -> a #

toList :: ListSplat a -> [a] #

null :: ListSplat a -> Bool #

length :: ListSplat a -> Int #

elem :: Eq a => a -> ListSplat a -> Bool #

maximum :: Ord a => ListSplat a -> a #

minimum :: Ord a => ListSplat a -> a #

sum :: Num a => ListSplat a -> a #

product :: Num a => ListSplat a -> a #

Traversable ListSplat Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ListSplat a -> f (ListSplat b) #

sequenceA :: Applicative f => ListSplat (f a) -> f (ListSplat a) #

mapM :: Monad m => (a -> m b) -> ListSplat a -> m (ListSplat b) #

sequence :: Monad m => ListSplat (m a) -> m (ListSplat a) #

SymbolMatching ListSplat Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy ListSplat -> Node -> Bool

showFailure :: Proxy ListSplat -> Node -> String

Unmarshal ListSplat Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ListSplat a)

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 #

Generic1 ListSplat Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ListSplat :: k -> Type #

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.5.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)))))
type Rep1 ListSplat Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ListSplat = D1 (MetaData "ListSplat" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ListSplat" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Maybe :.: Rec1 Expression)))

data DictionarySplat a Source #

Constructors

DictionarySplat 

Fields

Instances
Functor DictionarySplat Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> DictionarySplat a -> DictionarySplat b #

(<$) :: a -> DictionarySplat b -> DictionarySplat a #

Foldable DictionarySplat Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => DictionarySplat m -> m #

foldMap :: Monoid m => (a -> m) -> DictionarySplat a -> m #

foldr :: (a -> b -> b) -> b -> DictionarySplat a -> b #

foldr' :: (a -> b -> b) -> b -> DictionarySplat a -> b #

foldl :: (b -> a -> b) -> b -> DictionarySplat a -> b #

foldl' :: (b -> a -> b) -> b -> DictionarySplat a -> b #

foldr1 :: (a -> a -> a) -> DictionarySplat a -> a #

foldl1 :: (a -> a -> a) -> DictionarySplat a -> a #

toList :: DictionarySplat a -> [a] #

null :: DictionarySplat a -> Bool #

length :: DictionarySplat a -> Int #

elem :: Eq a => a -> DictionarySplat a -> Bool #

maximum :: Ord a => DictionarySplat a -> a #

minimum :: Ord a => DictionarySplat a -> a #

sum :: Num a => DictionarySplat a -> a #

product :: Num a => DictionarySplat a -> a #

Traversable DictionarySplat Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> DictionarySplat a -> f (DictionarySplat b) #

sequenceA :: Applicative f => DictionarySplat (f a) -> f (DictionarySplat a) #

mapM :: Monad m => (a -> m b) -> DictionarySplat a -> m (DictionarySplat b) #

sequence :: Monad m => DictionarySplat (m a) -> m (DictionarySplat a) #

SymbolMatching DictionarySplat Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal DictionarySplat Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (DictionarySplat a)

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 #

Generic1 DictionarySplat Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 DictionarySplat :: k -> Type #

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.5.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))))
type Rep1 DictionarySplat Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 DictionarySplat = D1 (MetaData "DictionarySplat" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "DictionarySplat" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Expression)))

data TypedDefaultParameter a Source #

Constructors

TypedDefaultParameter 

Fields

Instances
Functor TypedDefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable TypedDefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => TypedDefaultParameter m -> m #

foldMap :: Monoid m => (a -> m) -> TypedDefaultParameter a -> m #

foldr :: (a -> b -> b) -> b -> TypedDefaultParameter a -> b #

foldr' :: (a -> b -> b) -> b -> TypedDefaultParameter a -> b #

foldl :: (b -> a -> b) -> b -> TypedDefaultParameter a -> b #

foldl' :: (b -> a -> b) -> b -> TypedDefaultParameter a -> b #

foldr1 :: (a -> a -> a) -> TypedDefaultParameter a -> a #

foldl1 :: (a -> a -> a) -> TypedDefaultParameter a -> a #

toList :: TypedDefaultParameter a -> [a] #

null :: TypedDefaultParameter a -> Bool #

length :: TypedDefaultParameter a -> Int #

elem :: Eq a => a -> TypedDefaultParameter a -> Bool #

maximum :: Ord a => TypedDefaultParameter a -> a #

minimum :: Ord a => TypedDefaultParameter a -> a #

sum :: Num a => TypedDefaultParameter a -> a #

product :: Num a => TypedDefaultParameter a -> a #

Traversable TypedDefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching TypedDefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal TypedDefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (TypedDefaultParameter a)

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 #

Generic1 TypedDefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 TypedDefaultParameter :: k -> Type #

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.5.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)))))
type Rep1 TypedDefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

data DefaultParameter a Source #

Constructors

DefaultParameter 

Fields

Instances
Functor DefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> DefaultParameter a -> DefaultParameter b #

(<$) :: a -> DefaultParameter b -> DefaultParameter a #

Foldable DefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => DefaultParameter m -> m #

foldMap :: Monoid m => (a -> m) -> DefaultParameter a -> m #

foldr :: (a -> b -> b) -> b -> DefaultParameter a -> b #

foldr' :: (a -> b -> b) -> b -> DefaultParameter a -> b #

foldl :: (b -> a -> b) -> b -> DefaultParameter a -> b #

foldl' :: (b -> a -> b) -> b -> DefaultParameter a -> b #

foldr1 :: (a -> a -> a) -> DefaultParameter a -> a #

foldl1 :: (a -> a -> a) -> DefaultParameter a -> a #

toList :: DefaultParameter a -> [a] #

null :: DefaultParameter a -> Bool #

length :: DefaultParameter a -> Int #

elem :: Eq a => a -> DefaultParameter a -> Bool #

maximum :: Ord a => DefaultParameter a -> a #

minimum :: Ord a => DefaultParameter a -> a #

sum :: Num a => DefaultParameter a -> a #

product :: Num a => DefaultParameter a -> a #

Traversable DefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> DefaultParameter a -> f (DefaultParameter b) #

sequenceA :: Applicative f => DefaultParameter (f a) -> f (DefaultParameter a) #

mapM :: Monad m => (a -> m b) -> DefaultParameter a -> m (DefaultParameter b) #

sequence :: Monad m => DefaultParameter (m a) -> m (DefaultParameter a) #

SymbolMatching DefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal DefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (DefaultParameter a)

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 #

Generic1 DefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 DefaultParameter :: k -> Type #

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.5.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)))))
type Rep1 DefaultParameter Source # 
Instance details

Defined in TreeSitter.Python.AST

data ConditionalExpression a Source #

Constructors

ConditionalExpression 

Fields

Instances
Functor ConditionalExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable ConditionalExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ConditionalExpression m -> m #

foldMap :: Monoid m => (a -> m) -> ConditionalExpression a -> m #

foldr :: (a -> b -> b) -> b -> ConditionalExpression a -> b #

foldr' :: (a -> b -> b) -> b -> ConditionalExpression a -> b #

foldl :: (b -> a -> b) -> b -> ConditionalExpression a -> b #

foldl' :: (b -> a -> b) -> b -> ConditionalExpression a -> b #

foldr1 :: (a -> a -> a) -> ConditionalExpression a -> a #

foldl1 :: (a -> a -> a) -> ConditionalExpression a -> a #

toList :: ConditionalExpression a -> [a] #

null :: ConditionalExpression a -> Bool #

length :: ConditionalExpression a -> Int #

elem :: Eq a => a -> ConditionalExpression a -> Bool #

maximum :: Ord a => ConditionalExpression a -> a #

minimum :: Ord a => ConditionalExpression a -> a #

sum :: Num a => ConditionalExpression a -> a #

product :: Num a => ConditionalExpression a -> a #

Traversable ConditionalExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching ConditionalExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ConditionalExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ConditionalExpression a)

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 #

Generic1 ConditionalExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ConditionalExpression :: k -> Type #

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.5.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)))))
type Rep1 ConditionalExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ConditionalExpression = D1 (MetaData "ConditionalExpression" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ConditionalExpression" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 Expression)))

data ComparisonOperator a Source #

Constructors

ComparisonOperator 
Instances
Functor ComparisonOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable ComparisonOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ComparisonOperator m -> m #

foldMap :: Monoid m => (a -> m) -> ComparisonOperator a -> m #

foldr :: (a -> b -> b) -> b -> ComparisonOperator a -> b #

foldr' :: (a -> b -> b) -> b -> ComparisonOperator a -> b #

foldl :: (b -> a -> b) -> b -> ComparisonOperator a -> b #

foldl' :: (b -> a -> b) -> b -> ComparisonOperator a -> b #

foldr1 :: (a -> a -> a) -> ComparisonOperator a -> a #

foldl1 :: (a -> a -> a) -> ComparisonOperator a -> a #

toList :: ComparisonOperator a -> [a] #

null :: ComparisonOperator a -> Bool #

length :: ComparisonOperator a -> Int #

elem :: Eq a => a -> ComparisonOperator a -> Bool #

maximum :: Ord a => ComparisonOperator a -> a #

minimum :: Ord a => ComparisonOperator a -> a #

sum :: Num a => ComparisonOperator a -> a #

product :: Num a => ComparisonOperator a -> a #

Traversable ComparisonOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching ComparisonOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ComparisonOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ComparisonOperator a)

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 #

Generic1 ComparisonOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ComparisonOperator :: k -> Type #

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.5.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)))))
type Rep1 ComparisonOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ComparisonOperator = D1 (MetaData "ComparisonOperator" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ComparisonOperator" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 PrimaryExpression)))

data BooleanOperator a Source #

Constructors

BooleanOperator 
Instances
Functor BooleanOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> BooleanOperator a -> BooleanOperator b #

(<$) :: a -> BooleanOperator b -> BooleanOperator a #

Foldable BooleanOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => BooleanOperator m -> m #

foldMap :: Monoid m => (a -> m) -> BooleanOperator a -> m #

foldr :: (a -> b -> b) -> b -> BooleanOperator a -> b #

foldr' :: (a -> b -> b) -> b -> BooleanOperator a -> b #

foldl :: (b -> a -> b) -> b -> BooleanOperator a -> b #

foldl' :: (b -> a -> b) -> b -> BooleanOperator a -> b #

foldr1 :: (a -> a -> a) -> BooleanOperator a -> a #

foldl1 :: (a -> a -> a) -> BooleanOperator a -> a #

toList :: BooleanOperator a -> [a] #

null :: BooleanOperator a -> Bool #

length :: BooleanOperator a -> Int #

elem :: Eq a => a -> BooleanOperator a -> Bool #

maximum :: Ord a => BooleanOperator a -> a #

minimum :: Ord a => BooleanOperator a -> a #

sum :: Num a => BooleanOperator a -> a #

product :: Num a => BooleanOperator a -> a #

Traversable BooleanOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> BooleanOperator a -> f (BooleanOperator b) #

sequenceA :: Applicative f => BooleanOperator (f a) -> f (BooleanOperator a) #

mapM :: Monad m => (a -> m b) -> BooleanOperator a -> m (BooleanOperator b) #

sequence :: Monad m => BooleanOperator (m a) -> m (BooleanOperator a) #

SymbolMatching BooleanOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal BooleanOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (BooleanOperator a)

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 #

Generic1 BooleanOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 BooleanOperator :: k -> Type #

type Rep (BooleanOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 BooleanOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

data Await a Source #

Constructors

Await 

Fields

Instances
Functor Await Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Await a -> Await b #

(<$) :: a -> Await b -> Await a #

Foldable Await Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Await m -> m #

foldMap :: Monoid m => (a -> m) -> Await a -> m #

foldr :: (a -> b -> b) -> b -> Await a -> b #

foldr' :: (a -> b -> b) -> b -> Await a -> b #

foldl :: (b -> a -> b) -> b -> Await a -> b #

foldl' :: (b -> a -> b) -> b -> Await a -> b #

foldr1 :: (a -> a -> a) -> Await a -> a #

foldl1 :: (a -> a -> a) -> Await a -> a #

toList :: Await a -> [a] #

null :: Await a -> Bool #

length :: Await a -> Int #

elem :: Eq a => a -> Await a -> Bool #

maximum :: Ord a => Await a -> a #

minimum :: Ord a => Await a -> a #

sum :: Num a => Await a -> a #

product :: Num a => Await a -> a #

Traversable Await Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Await a -> f (Await b) #

sequenceA :: Applicative f => Await (f a) -> f (Await a) #

mapM :: Monad m => (a -> m b) -> Await a -> m (Await b) #

sequence :: Monad m => Await (m a) -> m (Await a) #

SymbolMatching Await Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Await -> Node -> Bool

showFailure :: Proxy Await -> Node -> String

Unmarshal Await Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Await a)

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 #

Generic1 Await Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Await :: k -> Type #

Methods

from1 :: Await a -> Rep1 Await a #

to1 :: Rep1 Await a -> Await a #

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.5.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))))
type Rep1 Await Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Await = D1 (MetaData "Await" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Await" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Expression)))

data Subscript a Source #

Instances
Functor Subscript Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Subscript a -> Subscript b #

(<$) :: a -> Subscript b -> Subscript a #

Foldable Subscript Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Subscript m -> m #

foldMap :: Monoid m => (a -> m) -> Subscript a -> m #

foldr :: (a -> b -> b) -> b -> Subscript a -> b #

foldr' :: (a -> b -> b) -> b -> Subscript a -> b #

foldl :: (b -> a -> b) -> b -> Subscript a -> b #

foldl' :: (b -> a -> b) -> b -> Subscript a -> b #

foldr1 :: (a -> a -> a) -> Subscript a -> a #

foldl1 :: (a -> a -> a) -> Subscript a -> a #

toList :: Subscript a -> [a] #

null :: Subscript a -> Bool #

length :: Subscript a -> Int #

elem :: Eq a => a -> Subscript a -> Bool #

maximum :: Ord a => Subscript a -> a #

minimum :: Ord a => Subscript a -> a #

sum :: Num a => Subscript a -> a #

product :: Num a => Subscript a -> a #

Traversable Subscript Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Subscript a -> f (Subscript b) #

sequenceA :: Applicative f => Subscript (f a) -> f (Subscript a) #

mapM :: Monad m => (a -> m b) -> Subscript a -> m (Subscript b) #

sequence :: Monad m => Subscript (m a) -> m (Subscript a) #

SymbolMatching Subscript Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Subscript -> Node -> Bool

showFailure :: Proxy Subscript -> Node -> String

Unmarshal Subscript Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Subscript a)

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 #

Generic1 Subscript Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Subscript :: k -> Type #

type Rep (Subscript a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Subscript Source # 
Instance details

Defined in TreeSitter.Python.AST

data Slice a Source #

Constructors

Slice 

Fields

Instances
Functor Slice Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Slice a -> Slice b #

(<$) :: a -> Slice b -> Slice a #

Foldable Slice Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Slice m -> m #

foldMap :: Monoid m => (a -> m) -> Slice a -> m #

foldr :: (a -> b -> b) -> b -> Slice a -> b #

foldr' :: (a -> b -> b) -> b -> Slice a -> b #

foldl :: (b -> a -> b) -> b -> Slice a -> b #

foldl' :: (b -> a -> b) -> b -> Slice a -> b #

foldr1 :: (a -> a -> a) -> Slice a -> a #

foldl1 :: (a -> a -> a) -> Slice a -> a #

toList :: Slice a -> [a] #

null :: Slice a -> Bool #

length :: Slice a -> Int #

elem :: Eq a => a -> Slice a -> Bool #

maximum :: Ord a => Slice a -> a #

minimum :: Ord a => Slice a -> a #

sum :: Num a => Slice a -> a #

product :: Num a => Slice a -> a #

Traversable Slice Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Slice a -> f (Slice b) #

sequenceA :: Applicative f => Slice (f a) -> f (Slice a) #

mapM :: Monad m => (a -> m b) -> Slice a -> m (Slice b) #

sequence :: Monad m => Slice (m a) -> m (Slice a) #

SymbolMatching Slice Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Slice -> Node -> Bool

showFailure :: Proxy Slice -> Node -> String

Unmarshal Slice Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Slice a)

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 #

Generic1 Slice Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Slice :: k -> Type #

Methods

from1 :: Slice a -> Rep1 Slice a #

to1 :: Rep1 Slice a -> Slice a #

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.5.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])))
type Rep1 Slice Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Slice = D1 (MetaData "Slice" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Slice" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 Expression)))

data String a Source #

Constructors

String 
Instances
Functor String Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> String a -> String b #

(<$) :: a -> String b -> String a #

Foldable String Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => String m -> m #

foldMap :: Monoid m => (a -> m) -> String a -> m #

foldr :: (a -> b -> b) -> b -> String a -> b #

foldr' :: (a -> b -> b) -> b -> String a -> b #

foldl :: (b -> a -> b) -> b -> String a -> b #

foldl' :: (b -> a -> b) -> b -> String a -> b #

foldr1 :: (a -> a -> a) -> String a -> a #

foldl1 :: (a -> a -> a) -> String a -> a #

toList :: String a -> [a] #

null :: String a -> Bool #

length :: String a -> Int #

elem :: Eq a => a -> String a -> Bool #

maximum :: Ord a => String a -> a #

minimum :: Ord a => String a -> a #

sum :: Num a => String a -> a #

product :: Num a => String a -> a #

Traversable String Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> String a -> f (String b) #

sequenceA :: Applicative f => String (f a) -> f (String a) #

mapM :: Monad m => (a -> m b) -> String a -> m (String b) #

sequence :: Monad m => String (m a) -> m (String a) #

SymbolMatching String Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy String -> Node -> Bool

showFailure :: Proxy String -> Node -> String0

Unmarshal String Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (String a)

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 #

Generic1 String Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 String :: k -> Type #

Methods

from1 :: String a -> Rep1 String a #

to1 :: Rep1 String a -> String a #

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.5.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 [(EscapeSequence :+: Interpolation) a])))
type Rep1 String Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 String = D1 (MetaData "String" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "String" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 (EscapeSequence :+: Interpolation))))

data Interpolation a Source #

Instances
Functor Interpolation Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Interpolation a -> Interpolation b #

(<$) :: a -> Interpolation b -> Interpolation a #

Foldable Interpolation Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Interpolation m -> m #

foldMap :: Monoid m => (a -> m) -> Interpolation a -> m #

foldr :: (a -> b -> b) -> b -> Interpolation a -> b #

foldr' :: (a -> b -> b) -> b -> Interpolation a -> b #

foldl :: (b -> a -> b) -> b -> Interpolation a -> b #

foldl' :: (b -> a -> b) -> b -> Interpolation a -> b #

foldr1 :: (a -> a -> a) -> Interpolation a -> a #

foldl1 :: (a -> a -> a) -> Interpolation a -> a #

toList :: Interpolation a -> [a] #

null :: Interpolation a -> Bool #

length :: Interpolation a -> Int #

elem :: Eq a => a -> Interpolation a -> Bool #

maximum :: Ord a => Interpolation a -> a #

minimum :: Ord a => Interpolation a -> a #

sum :: Num a => Interpolation a -> a #

product :: Num a => Interpolation a -> a #

Traversable Interpolation Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Interpolation a -> f (Interpolation b) #

sequenceA :: Applicative f => Interpolation (f a) -> f (Interpolation a) #

mapM :: Monad m => (a -> m b) -> Interpolation a -> m (Interpolation b) #

sequence :: Monad m => Interpolation (m a) -> m (Interpolation a) #

SymbolMatching Interpolation Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal Interpolation Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Interpolation a)

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 #

Generic1 Interpolation Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Interpolation :: k -> Type #

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.5.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 ((Expression :+: (FormatSpecifier :+: TypeConversion)) a)))))
type Rep1 Interpolation Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Interpolation = D1 (MetaData "Interpolation" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Interpolation" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 (Expression :+: (FormatSpecifier :+: TypeConversion)))))

data FormatSpecifier a Source #

Constructors

FormatSpecifier 

Fields

Instances
Functor FormatSpecifier Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> FormatSpecifier a -> FormatSpecifier b #

(<$) :: a -> FormatSpecifier b -> FormatSpecifier a #

Foldable FormatSpecifier Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => FormatSpecifier m -> m #

foldMap :: Monoid m => (a -> m) -> FormatSpecifier a -> m #

foldr :: (a -> b -> b) -> b -> FormatSpecifier a -> b #

foldr' :: (a -> b -> b) -> b -> FormatSpecifier a -> b #

foldl :: (b -> a -> b) -> b -> FormatSpecifier a -> b #

foldl' :: (b -> a -> b) -> b -> FormatSpecifier a -> b #

foldr1 :: (a -> a -> a) -> FormatSpecifier a -> a #

foldl1 :: (a -> a -> a) -> FormatSpecifier a -> a #

toList :: FormatSpecifier a -> [a] #

null :: FormatSpecifier a -> Bool #

length :: FormatSpecifier a -> Int #

elem :: Eq a => a -> FormatSpecifier a -> Bool #

maximum :: Ord a => FormatSpecifier a -> a #

minimum :: Ord a => FormatSpecifier a -> a #

sum :: Num a => FormatSpecifier a -> a #

product :: Num a => FormatSpecifier a -> a #

Traversable FormatSpecifier Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> FormatSpecifier a -> f (FormatSpecifier b) #

sequenceA :: Applicative f => FormatSpecifier (f a) -> f (FormatSpecifier a) #

mapM :: Monad m => (a -> m b) -> FormatSpecifier a -> m (FormatSpecifier b) #

sequence :: Monad m => FormatSpecifier (m a) -> m (FormatSpecifier a) #

SymbolMatching FormatSpecifier Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal FormatSpecifier Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (FormatSpecifier a)

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 #

Generic1 FormatSpecifier Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 FormatSpecifier :: k -> Type #

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.5.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])))
type Rep1 FormatSpecifier Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 FormatSpecifier = D1 (MetaData "FormatSpecifier" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "FormatSpecifier" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 FormatExpression)))

data FormatExpression a Source #

Constructors

FormatExpression 

Fields

Instances
Functor FormatExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> FormatExpression a -> FormatExpression b #

(<$) :: a -> FormatExpression b -> FormatExpression a #

Foldable FormatExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => FormatExpression m -> m #

foldMap :: Monoid m => (a -> m) -> FormatExpression a -> m #

foldr :: (a -> b -> b) -> b -> FormatExpression a -> b #

foldr' :: (a -> b -> b) -> b -> FormatExpression a -> b #

foldl :: (b -> a -> b) -> b -> FormatExpression a -> b #

foldl' :: (b -> a -> b) -> b -> FormatExpression a -> b #

foldr1 :: (a -> a -> a) -> FormatExpression a -> a #

foldl1 :: (a -> a -> a) -> FormatExpression a -> a #

toList :: FormatExpression a -> [a] #

null :: FormatExpression a -> Bool #

length :: FormatExpression a -> Int #

elem :: Eq a => a -> FormatExpression a -> Bool #

maximum :: Ord a => FormatExpression a -> a #

minimum :: Ord a => FormatExpression a -> a #

sum :: Num a => FormatExpression a -> a #

product :: Num a => FormatExpression a -> a #

Traversable FormatExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> FormatExpression a -> f (FormatExpression b) #

sequenceA :: Applicative f => FormatExpression (f a) -> f (FormatExpression a) #

mapM :: Monad m => (a -> m b) -> FormatExpression a -> m (FormatExpression b) #

sequence :: Monad m => FormatExpression (m a) -> m (FormatExpression a) #

SymbolMatching FormatExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal FormatExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (FormatExpression a)

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 #

Generic1 FormatExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 FormatExpression :: k -> Type #

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.5.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))))
type Rep1 FormatExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 FormatExpression = D1 (MetaData "FormatExpression" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "FormatExpression" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Expression)))

data SetComprehension a Source #

Constructors

SetComprehension 
Instances
Functor SetComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> SetComprehension a -> SetComprehension b #

(<$) :: a -> SetComprehension b -> SetComprehension a #

Foldable SetComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => SetComprehension m -> m #

foldMap :: Monoid m => (a -> m) -> SetComprehension a -> m #

foldr :: (a -> b -> b) -> b -> SetComprehension a -> b #

foldr' :: (a -> b -> b) -> b -> SetComprehension a -> b #

foldl :: (b -> a -> b) -> b -> SetComprehension a -> b #

foldl' :: (b -> a -> b) -> b -> SetComprehension a -> b #

foldr1 :: (a -> a -> a) -> SetComprehension a -> a #

foldl1 :: (a -> a -> a) -> SetComprehension a -> a #

toList :: SetComprehension a -> [a] #

null :: SetComprehension a -> Bool #

length :: SetComprehension a -> Int #

elem :: Eq a => a -> SetComprehension a -> Bool #

maximum :: Ord a => SetComprehension a -> a #

minimum :: Ord a => SetComprehension a -> a #

sum :: Num a => SetComprehension a -> a #

product :: Num a => SetComprehension a -> a #

Traversable SetComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> SetComprehension a -> f (SetComprehension b) #

sequenceA :: Applicative f => SetComprehension (f a) -> f (SetComprehension a) #

mapM :: Monad m => (a -> m b) -> SetComprehension a -> m (SetComprehension b) #

sequence :: Monad m => SetComprehension (m a) -> m (SetComprehension a) #

SymbolMatching SetComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal SetComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (SetComprehension a)

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 #

Generic1 SetComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 SetComprehension :: k -> Type #

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.5.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 ((ForInClause :+: IfClause) a))))))
type Rep1 SetComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

data IfClause a Source #

Constructors

IfClause 

Fields

Instances
Functor IfClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> IfClause a -> IfClause b #

(<$) :: a -> IfClause b -> IfClause a #

Foldable IfClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => IfClause m -> m #

foldMap :: Monoid m => (a -> m) -> IfClause a -> m #

foldr :: (a -> b -> b) -> b -> IfClause a -> b #

foldr' :: (a -> b -> b) -> b -> IfClause a -> b #

foldl :: (b -> a -> b) -> b -> IfClause a -> b #

foldl' :: (b -> a -> b) -> b -> IfClause a -> b #

foldr1 :: (a -> a -> a) -> IfClause a -> a #

foldl1 :: (a -> a -> a) -> IfClause a -> a #

toList :: IfClause a -> [a] #

null :: IfClause a -> Bool #

length :: IfClause a -> Int #

elem :: Eq a => a -> IfClause a -> Bool #

maximum :: Ord a => IfClause a -> a #

minimum :: Ord a => IfClause a -> a #

sum :: Num a => IfClause a -> a #

product :: Num a => IfClause a -> a #

Traversable IfClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> IfClause a -> f (IfClause b) #

sequenceA :: Applicative f => IfClause (f a) -> f (IfClause a) #

mapM :: Monad m => (a -> m b) -> IfClause a -> m (IfClause b) #

sequence :: Monad m => IfClause (m a) -> m (IfClause a) #

SymbolMatching IfClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy IfClause -> Node -> Bool

showFailure :: Proxy IfClause -> Node -> String

Unmarshal IfClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (IfClause a)

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 #

Generic1 IfClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 IfClause :: k -> Type #

Methods

from1 :: IfClause a -> Rep1 IfClause a #

to1 :: Rep1 IfClause a -> IfClause a #

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.5.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))))
type Rep1 IfClause Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 IfClause = D1 (MetaData "IfClause" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "IfClause" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Expression)))

data ForInClause a Source #

Constructors

ForInClause 
Instances
Functor ForInClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> ForInClause a -> ForInClause b #

(<$) :: a -> ForInClause b -> ForInClause a #

Foldable ForInClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ForInClause m -> m #

foldMap :: Monoid m => (a -> m) -> ForInClause a -> m #

foldr :: (a -> b -> b) -> b -> ForInClause a -> b #

foldr' :: (a -> b -> b) -> b -> ForInClause a -> b #

foldl :: (b -> a -> b) -> b -> ForInClause a -> b #

foldl' :: (b -> a -> b) -> b -> ForInClause a -> b #

foldr1 :: (a -> a -> a) -> ForInClause a -> a #

foldl1 :: (a -> a -> a) -> ForInClause a -> a #

toList :: ForInClause a -> [a] #

null :: ForInClause a -> Bool #

length :: ForInClause a -> Int #

elem :: Eq a => a -> ForInClause a -> Bool #

maximum :: Ord a => ForInClause a -> a #

minimum :: Ord a => ForInClause a -> a #

sum :: Num a => ForInClause a -> a #

product :: Num a => ForInClause a -> a #

Traversable ForInClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ForInClause a -> f (ForInClause b) #

sequenceA :: Applicative f => ForInClause (f a) -> f (ForInClause a) #

mapM :: Monad m => (a -> m b) -> ForInClause a -> m (ForInClause b) #

sequence :: Monad m => ForInClause (m a) -> m (ForInClause a) #

SymbolMatching ForInClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ForInClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ForInClause a)

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 #

Generic1 ForInClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ForInClause :: k -> Type #

type Rep (ForInClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ForInClause Source # 
Instance details

Defined in TreeSitter.Python.AST

data Variables a Source #

Constructors

Variables 
Instances
Functor Variables Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Variables a -> Variables b #

(<$) :: a -> Variables b -> Variables a #

Foldable Variables Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Variables m -> m #

foldMap :: Monoid m => (a -> m) -> Variables a -> m #

foldr :: (a -> b -> b) -> b -> Variables a -> b #

foldr' :: (a -> b -> b) -> b -> Variables a -> b #

foldl :: (b -> a -> b) -> b -> Variables a -> b #

foldl' :: (b -> a -> b) -> b -> Variables a -> b #

foldr1 :: (a -> a -> a) -> Variables a -> a #

foldl1 :: (a -> a -> a) -> Variables a -> a #

toList :: Variables a -> [a] #

null :: Variables a -> Bool #

length :: Variables a -> Int #

elem :: Eq a => a -> Variables a -> Bool #

maximum :: Ord a => Variables a -> a #

minimum :: Ord a => Variables a -> a #

sum :: Num a => Variables a -> a #

product :: Num a => Variables a -> a #

Traversable Variables Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Variables a -> f (Variables b) #

sequenceA :: Applicative f => Variables (f a) -> f (Variables a) #

mapM :: Monad m => (a -> m b) -> Variables a -> m (Variables b) #

sequence :: Monad m => Variables (m a) -> m (Variables a) #

SymbolMatching Variables Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Variables -> Node -> Bool

showFailure :: Proxy Variables -> Node -> String

Unmarshal Variables Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Variables a)

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 #

Generic1 Variables Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Variables :: k -> Type #

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.5.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)))))
type Rep1 Variables Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Variables = D1 (MetaData "Variables" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Variables" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 PrimaryExpression)))

data Set a Source #

Constructors

Set 
Instances
Functor Set Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Set a -> Set b #

(<$) :: a -> Set b -> Set a #

Foldable Set Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Set m -> m #

foldMap :: Monoid m => (a -> m) -> Set a -> m #

foldr :: (a -> b -> b) -> b -> Set a -> b #

foldr' :: (a -> b -> b) -> b -> Set a -> b #

foldl :: (b -> a -> b) -> b -> Set a -> b #

foldl' :: (b -> a -> b) -> b -> Set a -> b #

foldr1 :: (a -> a -> a) -> Set a -> a #

foldl1 :: (a -> a -> a) -> Set a -> a #

toList :: Set a -> [a] #

null :: Set a -> Bool #

length :: Set a -> Int #

elem :: Eq a => a -> Set a -> Bool #

maximum :: Ord a => Set a -> a #

minimum :: Ord a => Set a -> a #

sum :: Num a => Set a -> a #

product :: Num a => Set a -> a #

Traversable Set Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Set a -> f (Set b) #

sequenceA :: Applicative f => Set (f a) -> f (Set a) #

mapM :: Monad m => (a -> m b) -> Set a -> m (Set b) #

sequence :: Monad m => Set (m a) -> m (Set a) #

SymbolMatching Set Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Set -> Node -> Bool

showFailure :: Proxy Set -> Node -> String

Unmarshal Set Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Set a)

Eq a => Eq (Set a) Source # 
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 #

Generic1 Set Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Set :: k -> Type #

Methods

from1 :: Set a -> Rep1 Set a #

to1 :: Rep1 Set a -> Set a #

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.5.0.0-inplace" False) (C1 (MetaCons "Set" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty ((Expression :+: ListSplat) a)))))
type Rep1 Set Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Set = D1 (MetaData "Set" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Set" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 (Expression :+: ListSplat))))

data ParenthesizedExpression a Source #

Instances
Functor ParenthesizedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable ParenthesizedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ParenthesizedExpression m -> m #

foldMap :: Monoid m => (a -> m) -> ParenthesizedExpression a -> m #

foldr :: (a -> b -> b) -> b -> ParenthesizedExpression a -> b #

foldr' :: (a -> b -> b) -> b -> ParenthesizedExpression a -> b #

foldl :: (b -> a -> b) -> b -> ParenthesizedExpression a -> b #

foldl' :: (b -> a -> b) -> b -> ParenthesizedExpression a -> b #

foldr1 :: (a -> a -> a) -> ParenthesizedExpression a -> a #

foldl1 :: (a -> a -> a) -> ParenthesizedExpression a -> a #

toList :: ParenthesizedExpression a -> [a] #

null :: ParenthesizedExpression a -> Bool #

length :: ParenthesizedExpression a -> Int #

elem :: Eq a => a -> ParenthesizedExpression a -> Bool #

maximum :: Ord a => ParenthesizedExpression a -> a #

minimum :: Ord a => ParenthesizedExpression a -> a #

sum :: Num a => ParenthesizedExpression a -> a #

product :: Num a => ParenthesizedExpression a -> a #

Traversable ParenthesizedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching ParenthesizedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ParenthesizedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ParenthesizedExpression a)

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 #

Generic1 ParenthesizedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ParenthesizedExpression :: k -> Type #

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.5.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 ((Expression :+: Yield) a))))
type Rep1 ParenthesizedExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ParenthesizedExpression = D1 (MetaData "ParenthesizedExpression" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ParenthesizedExpression" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 (Expression :+: Yield))))

data ListComprehension a Source #

Instances
Functor ListComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable ListComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ListComprehension m -> m #

foldMap :: Monoid m => (a -> m) -> ListComprehension a -> m #

foldr :: (a -> b -> b) -> b -> ListComprehension a -> b #

foldr' :: (a -> b -> b) -> b -> ListComprehension a -> b #

foldl :: (b -> a -> b) -> b -> ListComprehension a -> b #

foldl' :: (b -> a -> b) -> b -> ListComprehension a -> b #

foldr1 :: (a -> a -> a) -> ListComprehension a -> a #

foldl1 :: (a -> a -> a) -> ListComprehension a -> a #

toList :: ListComprehension a -> [a] #

null :: ListComprehension a -> Bool #

length :: ListComprehension a -> Int #

elem :: Eq a => a -> ListComprehension a -> Bool #

maximum :: Ord a => ListComprehension a -> a #

minimum :: Ord a => ListComprehension a -> a #

sum :: Num a => ListComprehension a -> a #

product :: Num a => ListComprehension a -> a #

Traversable ListComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ListComprehension a -> f (ListComprehension b) #

sequenceA :: Applicative f => ListComprehension (f a) -> f (ListComprehension a) #

mapM :: Monad m => (a -> m b) -> ListComprehension a -> m (ListComprehension b) #

sequence :: Monad m => ListComprehension (m a) -> m (ListComprehension a) #

SymbolMatching ListComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ListComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ListComprehension a)

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 #

Generic1 ListComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ListComprehension :: k -> Type #

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.5.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 ((ForInClause :+: IfClause) a))))))
type Rep1 ListComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

data List a Source #

Constructors

List 

Fields

Instances
Functor List Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> List a -> List b #

(<$) :: a -> List b -> List a #

Foldable List Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => List m -> m #

foldMap :: Monoid m => (a -> m) -> List a -> m #

foldr :: (a -> b -> b) -> b -> List a -> b #

foldr' :: (a -> b -> b) -> b -> List a -> b #

foldl :: (b -> a -> b) -> b -> List a -> b #

foldl' :: (b -> a -> b) -> b -> List a -> b #

foldr1 :: (a -> a -> a) -> List a -> a #

foldl1 :: (a -> a -> a) -> List a -> a #

toList :: List a -> [a] #

null :: List a -> Bool #

length :: List a -> Int #

elem :: Eq a => a -> List a -> Bool #

maximum :: Ord a => List a -> a #

minimum :: Ord a => List a -> a #

sum :: Num a => List a -> a #

product :: Num a => List a -> a #

Traversable List Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> List a -> f (List b) #

sequenceA :: Applicative f => List (f a) -> f (List a) #

mapM :: Monad m => (a -> m b) -> List a -> m (List b) #

sequence :: Monad m => List (m a) -> m (List a) #

SymbolMatching List Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy List -> Node -> Bool

showFailure :: Proxy List -> Node -> String

Unmarshal List Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (List a)

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 #

Generic1 List Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 List :: k -> Type #

Methods

from1 :: List a -> Rep1 List a #

to1 :: Rep1 List a -> List a #

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.5.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 [(Expression :+: ListSplat) a])))
type Rep1 List Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 List = D1 (MetaData "List" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "List" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 (Expression :+: ListSplat))))

data GeneratorExpression a Source #

Instances
Functor GeneratorExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable GeneratorExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => GeneratorExpression m -> m #

foldMap :: Monoid m => (a -> m) -> GeneratorExpression a -> m #

foldr :: (a -> b -> b) -> b -> GeneratorExpression a -> b #

foldr' :: (a -> b -> b) -> b -> GeneratorExpression a -> b #

foldl :: (b -> a -> b) -> b -> GeneratorExpression a -> b #

foldl' :: (b -> a -> b) -> b -> GeneratorExpression a -> b #

foldr1 :: (a -> a -> a) -> GeneratorExpression a -> a #

foldl1 :: (a -> a -> a) -> GeneratorExpression a -> a #

toList :: GeneratorExpression a -> [a] #

null :: GeneratorExpression a -> Bool #

length :: GeneratorExpression a -> Int #

elem :: Eq a => a -> GeneratorExpression a -> Bool #

maximum :: Ord a => GeneratorExpression a -> a #

minimum :: Ord a => GeneratorExpression a -> a #

sum :: Num a => GeneratorExpression a -> a #

product :: Num a => GeneratorExpression a -> a #

Traversable GeneratorExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching GeneratorExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal GeneratorExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (GeneratorExpression a)

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 #

Generic1 GeneratorExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 GeneratorExpression :: k -> Type #

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.5.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 ((ForInClause :+: IfClause) a))))))
type Rep1 GeneratorExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 GeneratorExpression = D1 (MetaData "GeneratorExpression" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "GeneratorExpression" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: (S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Expression) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 (ForInClause :+: IfClause)))))

data DictionaryComprehension a Source #

Instances
Functor DictionaryComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable DictionaryComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => DictionaryComprehension m -> m #

foldMap :: Monoid m => (a -> m) -> DictionaryComprehension a -> m #

foldr :: (a -> b -> b) -> b -> DictionaryComprehension a -> b #

foldr' :: (a -> b -> b) -> b -> DictionaryComprehension a -> b #

foldl :: (b -> a -> b) -> b -> DictionaryComprehension a -> b #

foldl' :: (b -> a -> b) -> b -> DictionaryComprehension a -> b #

foldr1 :: (a -> a -> a) -> DictionaryComprehension a -> a #

foldl1 :: (a -> a -> a) -> DictionaryComprehension a -> a #

toList :: DictionaryComprehension a -> [a] #

null :: DictionaryComprehension a -> Bool #

length :: DictionaryComprehension a -> Int #

elem :: Eq a => a -> DictionaryComprehension a -> Bool #

maximum :: Ord a => DictionaryComprehension a -> a #

minimum :: Ord a => DictionaryComprehension a -> a #

sum :: Num a => DictionaryComprehension a -> a #

product :: Num a => DictionaryComprehension a -> a #

Traversable DictionaryComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching DictionaryComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal DictionaryComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (DictionaryComprehension a)

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 #

Generic1 DictionaryComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 DictionaryComprehension :: k -> Type #

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.5.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 ((ForInClause :+: IfClause) a))))))
type Rep1 DictionaryComprehension Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 DictionaryComprehension = D1 (MetaData "DictionaryComprehension" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "DictionaryComprehension" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: (S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Pair) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 (ForInClause :+: IfClause)))))

data Pair a Source #

Constructors

Pair 

Fields

Instances
Functor Pair Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Pair a -> Pair b #

(<$) :: a -> Pair b -> Pair a #

Foldable Pair Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Pair m -> m #

foldMap :: Monoid m => (a -> m) -> Pair a -> m #

foldr :: (a -> b -> b) -> b -> Pair a -> b #

foldr' :: (a -> b -> b) -> b -> Pair a -> b #

foldl :: (b -> a -> b) -> b -> Pair a -> b #

foldl' :: (b -> a -> b) -> b -> Pair a -> b #

foldr1 :: (a -> a -> a) -> Pair a -> a #

foldl1 :: (a -> a -> a) -> Pair a -> a #

toList :: Pair a -> [a] #

null :: Pair a -> Bool #

length :: Pair a -> Int #

elem :: Eq a => a -> Pair a -> Bool #

maximum :: Ord a => Pair a -> a #

minimum :: Ord a => Pair a -> a #

sum :: Num a => Pair a -> a #

product :: Num a => Pair a -> a #

Traversable Pair Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Pair a -> f (Pair b) #

sequenceA :: Applicative f => Pair (f a) -> f (Pair a) #

mapM :: Monad m => (a -> m b) -> Pair a -> m (Pair b) #

sequence :: Monad m => Pair (m a) -> m (Pair a) #

SymbolMatching Pair Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Pair -> Node -> Bool

showFailure :: Proxy Pair -> Node -> String

Unmarshal Pair Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Pair a)

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 #

Generic1 Pair Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Pair :: k -> Type #

Methods

from1 :: Pair a -> Rep1 Pair a #

to1 :: Rep1 Pair a -> Pair a #

type Rep (Pair a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Pair Source # 
Instance details

Defined in TreeSitter.Python.AST

data Dictionary a Source #

Constructors

Dictionary 

Fields

Instances
Functor Dictionary Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Dictionary a -> Dictionary b #

(<$) :: a -> Dictionary b -> Dictionary a #

Foldable Dictionary Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Dictionary m -> m #

foldMap :: Monoid m => (a -> m) -> Dictionary a -> m #

foldr :: (a -> b -> b) -> b -> Dictionary a -> b #

foldr' :: (a -> b -> b) -> b -> Dictionary a -> b #

foldl :: (b -> a -> b) -> b -> Dictionary a -> b #

foldl' :: (b -> a -> b) -> b -> Dictionary a -> b #

foldr1 :: (a -> a -> a) -> Dictionary a -> a #

foldl1 :: (a -> a -> a) -> Dictionary a -> a #

toList :: Dictionary a -> [a] #

null :: Dictionary a -> Bool #

length :: Dictionary a -> Int #

elem :: Eq a => a -> Dictionary a -> Bool #

maximum :: Ord a => Dictionary a -> a #

minimum :: Ord a => Dictionary a -> a #

sum :: Num a => Dictionary a -> a #

product :: Num a => Dictionary a -> a #

Traversable Dictionary Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Dictionary a -> f (Dictionary b) #

sequenceA :: Applicative f => Dictionary (f a) -> f (Dictionary a) #

mapM :: Monad m => (a -> m b) -> Dictionary a -> m (Dictionary b) #

sequence :: Monad m => Dictionary (m a) -> m (Dictionary a) #

SymbolMatching Dictionary Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal Dictionary Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Dictionary a)

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 #

Generic1 Dictionary Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Dictionary :: k -> Type #

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.5.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 [(DictionarySplat :+: Pair) a])))
type Rep1 Dictionary Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Dictionary = D1 (MetaData "Dictionary" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Dictionary" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 (DictionarySplat :+: Pair))))

data ConcatenatedString a Source #

Constructors

ConcatenatedString 

Fields

Instances
Functor ConcatenatedString Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable ConcatenatedString Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ConcatenatedString m -> m #

foldMap :: Monoid m => (a -> m) -> ConcatenatedString a -> m #

foldr :: (a -> b -> b) -> b -> ConcatenatedString a -> b #

foldr' :: (a -> b -> b) -> b -> ConcatenatedString a -> b #

foldl :: (b -> a -> b) -> b -> ConcatenatedString a -> b #

foldl' :: (b -> a -> b) -> b -> ConcatenatedString a -> b #

foldr1 :: (a -> a -> a) -> ConcatenatedString a -> a #

foldl1 :: (a -> a -> a) -> ConcatenatedString a -> a #

toList :: ConcatenatedString a -> [a] #

null :: ConcatenatedString a -> Bool #

length :: ConcatenatedString a -> Int #

elem :: Eq a => a -> ConcatenatedString a -> Bool #

maximum :: Ord a => ConcatenatedString a -> a #

minimum :: Ord a => ConcatenatedString a -> a #

sum :: Num a => ConcatenatedString a -> a #

product :: Num a => ConcatenatedString a -> a #

Traversable ConcatenatedString Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching ConcatenatedString Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ConcatenatedString Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ConcatenatedString a)

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 #

Generic1 ConcatenatedString Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ConcatenatedString :: k -> Type #

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.5.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)))))
type Rep1 ConcatenatedString Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ConcatenatedString = D1 (MetaData "ConcatenatedString" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ConcatenatedString" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 String)))

data Call a Source #

Instances
Functor Call Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Call a -> Call b #

(<$) :: a -> Call b -> Call a #

Foldable Call Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Call m -> m #

foldMap :: Monoid m => (a -> m) -> Call a -> m #

foldr :: (a -> b -> b) -> b -> Call a -> b #

foldr' :: (a -> b -> b) -> b -> Call a -> b #

foldl :: (b -> a -> b) -> b -> Call a -> b #

foldl' :: (b -> a -> b) -> b -> Call a -> b #

foldr1 :: (a -> a -> a) -> Call a -> a #

foldl1 :: (a -> a -> a) -> Call a -> a #

toList :: Call a -> [a] #

null :: Call a -> Bool #

length :: Call a -> Int #

elem :: Eq a => a -> Call a -> Bool #

maximum :: Ord a => Call a -> a #

minimum :: Ord a => Call a -> a #

sum :: Num a => Call a -> a #

product :: Num a => Call a -> a #

Traversable Call Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Call a -> f (Call b) #

sequenceA :: Applicative f => Call (f a) -> f (Call a) #

mapM :: Monad m => (a -> m b) -> Call a -> m (Call b) #

sequence :: Monad m => Call (m a) -> m (Call a) #

SymbolMatching Call Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Call -> Node -> Bool

showFailure :: Proxy Call -> Node -> String

Unmarshal Call Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Call a)

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 #

Generic1 Call Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Call :: k -> Type #

Methods

from1 :: Call a -> Rep1 Call a #

to1 :: Rep1 Call a -> Call a #

type Rep (Call a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Call Source # 
Instance details

Defined in TreeSitter.Python.AST

data ArgumentList a Source #

Instances
Functor ArgumentList Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> ArgumentList a -> ArgumentList b #

(<$) :: a -> ArgumentList b -> ArgumentList a #

Foldable ArgumentList Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ArgumentList m -> m #

foldMap :: Monoid m => (a -> m) -> ArgumentList a -> m #

foldr :: (a -> b -> b) -> b -> ArgumentList a -> b #

foldr' :: (a -> b -> b) -> b -> ArgumentList a -> b #

foldl :: (b -> a -> b) -> b -> ArgumentList a -> b #

foldl' :: (b -> a -> b) -> b -> ArgumentList a -> b #

foldr1 :: (a -> a -> a) -> ArgumentList a -> a #

foldl1 :: (a -> a -> a) -> ArgumentList a -> a #

toList :: ArgumentList a -> [a] #

null :: ArgumentList a -> Bool #

length :: ArgumentList a -> Int #

elem :: Eq a => a -> ArgumentList a -> Bool #

maximum :: Ord a => ArgumentList a -> a #

minimum :: Ord a => ArgumentList a -> a #

sum :: Num a => ArgumentList a -> a #

product :: Num a => ArgumentList a -> a #

Traversable ArgumentList Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ArgumentList a -> f (ArgumentList b) #

sequenceA :: Applicative f => ArgumentList (f a) -> f (ArgumentList a) #

mapM :: Monad m => (a -> m b) -> ArgumentList a -> m (ArgumentList b) #

sequence :: Monad m => ArgumentList (m a) -> m (ArgumentList a) #

SymbolMatching ArgumentList Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ArgumentList Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ArgumentList a)

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 #

Generic1 ArgumentList Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ArgumentList :: k -> Type #

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.5.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 [(Expression :+: (DictionarySplat :+: (KeywordArgument :+: ListSplat))) a])))
type Rep1 ArgumentList Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ArgumentList = D1 (MetaData "ArgumentList" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ArgumentList" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 (Expression :+: (DictionarySplat :+: (KeywordArgument :+: ListSplat))))))

data KeywordArgument a Source #

Constructors

KeywordArgument 

Fields

Instances
Functor KeywordArgument Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> KeywordArgument a -> KeywordArgument b #

(<$) :: a -> KeywordArgument b -> KeywordArgument a #

Foldable KeywordArgument Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => KeywordArgument m -> m #

foldMap :: Monoid m => (a -> m) -> KeywordArgument a -> m #

foldr :: (a -> b -> b) -> b -> KeywordArgument a -> b #

foldr' :: (a -> b -> b) -> b -> KeywordArgument a -> b #

foldl :: (b -> a -> b) -> b -> KeywordArgument a -> b #

foldl' :: (b -> a -> b) -> b -> KeywordArgument a -> b #

foldr1 :: (a -> a -> a) -> KeywordArgument a -> a #

foldl1 :: (a -> a -> a) -> KeywordArgument a -> a #

toList :: KeywordArgument a -> [a] #

null :: KeywordArgument a -> Bool #

length :: KeywordArgument a -> Int #

elem :: Eq a => a -> KeywordArgument a -> Bool #

maximum :: Ord a => KeywordArgument a -> a #

minimum :: Ord a => KeywordArgument a -> a #

sum :: Num a => KeywordArgument a -> a #

product :: Num a => KeywordArgument a -> a #

Traversable KeywordArgument Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> KeywordArgument a -> f (KeywordArgument b) #

sequenceA :: Applicative f => KeywordArgument (f a) -> f (KeywordArgument a) #

mapM :: Monad m => (a -> m b) -> KeywordArgument a -> m (KeywordArgument b) #

sequence :: Monad m => KeywordArgument (m a) -> m (KeywordArgument a) #

SymbolMatching KeywordArgument Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal KeywordArgument Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (KeywordArgument a)

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 #

Generic1 KeywordArgument Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 KeywordArgument :: k -> Type #

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.5.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)))))
type Rep1 KeywordArgument Source # 
Instance details

Defined in TreeSitter.Python.AST

data BinaryOperator a Source #

Instances
Functor BinaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> BinaryOperator a -> BinaryOperator b #

(<$) :: a -> BinaryOperator b -> BinaryOperator a #

Foldable BinaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => BinaryOperator m -> m #

foldMap :: Monoid m => (a -> m) -> BinaryOperator a -> m #

foldr :: (a -> b -> b) -> b -> BinaryOperator a -> b #

foldr' :: (a -> b -> b) -> b -> BinaryOperator a -> b #

foldl :: (b -> a -> b) -> b -> BinaryOperator a -> b #

foldl' :: (b -> a -> b) -> b -> BinaryOperator a -> b #

foldr1 :: (a -> a -> a) -> BinaryOperator a -> a #

foldl1 :: (a -> a -> a) -> BinaryOperator a -> a #

toList :: BinaryOperator a -> [a] #

null :: BinaryOperator a -> Bool #

length :: BinaryOperator a -> Int #

elem :: Eq a => a -> BinaryOperator a -> Bool #

maximum :: Ord a => BinaryOperator a -> a #

minimum :: Ord a => BinaryOperator a -> a #

sum :: Num a => BinaryOperator a -> a #

product :: Num a => BinaryOperator a -> a #

Traversable BinaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> BinaryOperator a -> f (BinaryOperator b) #

sequenceA :: Applicative f => BinaryOperator (f a) -> f (BinaryOperator a) #

mapM :: Monad m => (a -> m b) -> BinaryOperator a -> m (BinaryOperator b) #

sequence :: Monad m => BinaryOperator (m a) -> m (BinaryOperator a) #

SymbolMatching BinaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal BinaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (BinaryOperator a)

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 #

Generic1 BinaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 BinaryOperator :: k -> Type #

type Rep (BinaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 BinaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

data Attribute a Source #

Instances
Functor Attribute Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Attribute a -> Attribute b #

(<$) :: a -> Attribute b -> Attribute a #

Foldable Attribute Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Attribute m -> m #

foldMap :: Monoid m => (a -> m) -> Attribute a -> m #

foldr :: (a -> b -> b) -> b -> Attribute a -> b #

foldr' :: (a -> b -> b) -> b -> Attribute a -> b #

foldl :: (b -> a -> b) -> b -> Attribute a -> b #

foldl' :: (b -> a -> b) -> b -> Attribute a -> b #

foldr1 :: (a -> a -> a) -> Attribute a -> a #

foldl1 :: (a -> a -> a) -> Attribute a -> a #

toList :: Attribute a -> [a] #

null :: Attribute a -> Bool #

length :: Attribute a -> Int #

elem :: Eq a => a -> Attribute a -> Bool #

maximum :: Ord a => Attribute a -> a #

minimum :: Ord a => Attribute a -> a #

sum :: Num a => Attribute a -> a #

product :: Num a => Attribute a -> a #

Traversable Attribute Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Attribute a -> f (Attribute b) #

sequenceA :: Applicative f => Attribute (f a) -> f (Attribute a) #

mapM :: Monad m => (a -> m b) -> Attribute a -> m (Attribute b) #

sequence :: Monad m => Attribute (m a) -> m (Attribute a) #

SymbolMatching Attribute Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Attribute -> Node -> Bool

showFailure :: Proxy Attribute -> Node -> String

Unmarshal Attribute Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Attribute a)

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 #

Generic1 Attribute Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Attribute :: k -> Type #

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.5.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 ((PrimaryExpression :+: Identifier) a)))))
type Rep1 Attribute Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Attribute = D1 (MetaData "Attribute" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Attribute" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 (PrimaryExpression :+: Identifier))))

data WithItem a Source #

Constructors

WithItem 

Fields

Instances
Functor WithItem Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> WithItem a -> WithItem b #

(<$) :: a -> WithItem b -> WithItem a #

Foldable WithItem Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => WithItem m -> m #

foldMap :: Monoid m => (a -> m) -> WithItem a -> m #

foldr :: (a -> b -> b) -> b -> WithItem a -> b #

foldr' :: (a -> b -> b) -> b -> WithItem a -> b #

foldl :: (b -> a -> b) -> b -> WithItem a -> b #

foldl' :: (b -> a -> b) -> b -> WithItem a -> b #

foldr1 :: (a -> a -> a) -> WithItem a -> a #

foldl1 :: (a -> a -> a) -> WithItem a -> a #

toList :: WithItem a -> [a] #

null :: WithItem a -> Bool #

length :: WithItem a -> Int #

elem :: Eq a => a -> WithItem a -> Bool #

maximum :: Ord a => WithItem a -> a #

minimum :: Ord a => WithItem a -> a #

sum :: Num a => WithItem a -> a #

product :: Num a => WithItem a -> a #

Traversable WithItem Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> WithItem a -> f (WithItem b) #

sequenceA :: Applicative f => WithItem (f a) -> f (WithItem a) #

mapM :: Monad m => (a -> m b) -> WithItem a -> m (WithItem b) #

sequence :: Monad m => WithItem (m a) -> m (WithItem a) #

SymbolMatching WithItem Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy WithItem -> Node -> Bool

showFailure :: Proxy WithItem -> Node -> String

Unmarshal WithItem Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (WithItem a)

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 #

Generic1 WithItem Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 WithItem :: k -> Type #

Methods

from1 :: WithItem a -> Rep1 WithItem a #

to1 :: Rep1 WithItem a -> WithItem a #

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.5.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))))))
type Rep1 WithItem Source # 
Instance details

Defined in TreeSitter.Python.AST

data ReturnStatement a Source #

Constructors

ReturnStatement 

Fields

Instances
Functor ReturnStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> ReturnStatement a -> ReturnStatement b #

(<$) :: a -> ReturnStatement b -> ReturnStatement a #

Foldable ReturnStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ReturnStatement m -> m #

foldMap :: Monoid m => (a -> m) -> ReturnStatement a -> m #

foldr :: (a -> b -> b) -> b -> ReturnStatement a -> b #

foldr' :: (a -> b -> b) -> b -> ReturnStatement a -> b #

foldl :: (b -> a -> b) -> b -> ReturnStatement a -> b #

foldl' :: (b -> a -> b) -> b -> ReturnStatement a -> b #

foldr1 :: (a -> a -> a) -> ReturnStatement a -> a #

foldl1 :: (a -> a -> a) -> ReturnStatement a -> a #

toList :: ReturnStatement a -> [a] #

null :: ReturnStatement a -> Bool #

length :: ReturnStatement a -> Int #

elem :: Eq a => a -> ReturnStatement a -> Bool #

maximum :: Ord a => ReturnStatement a -> a #

minimum :: Ord a => ReturnStatement a -> a #

sum :: Num a => ReturnStatement a -> a #

product :: Num a => ReturnStatement a -> a #

Traversable ReturnStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ReturnStatement a -> f (ReturnStatement b) #

sequenceA :: Applicative f => ReturnStatement (f a) -> f (ReturnStatement a) #

mapM :: Monad m => (a -> m b) -> ReturnStatement a -> m (ReturnStatement b) #

sequence :: Monad m => ReturnStatement (m a) -> m (ReturnStatement a) #

SymbolMatching ReturnStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ReturnStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ReturnStatement a)

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 #

Generic1 ReturnStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ReturnStatement :: k -> Type #

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.5.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)))))
type Rep1 ReturnStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ReturnStatement = D1 (MetaData "ReturnStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ReturnStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Maybe :.: Rec1 ExpressionList)))

data RaiseStatement a Source #

Constructors

RaiseStatement 

Fields

Instances
Functor RaiseStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> RaiseStatement a -> RaiseStatement b #

(<$) :: a -> RaiseStatement b -> RaiseStatement a #

Foldable RaiseStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => RaiseStatement m -> m #

foldMap :: Monoid m => (a -> m) -> RaiseStatement a -> m #

foldr :: (a -> b -> b) -> b -> RaiseStatement a -> b #

foldr' :: (a -> b -> b) -> b -> RaiseStatement a -> b #

foldl :: (b -> a -> b) -> b -> RaiseStatement a -> b #

foldl' :: (b -> a -> b) -> b -> RaiseStatement a -> b #

foldr1 :: (a -> a -> a) -> RaiseStatement a -> a #

foldl1 :: (a -> a -> a) -> RaiseStatement a -> a #

toList :: RaiseStatement a -> [a] #

null :: RaiseStatement a -> Bool #

length :: RaiseStatement a -> Int #

elem :: Eq a => a -> RaiseStatement a -> Bool #

maximum :: Ord a => RaiseStatement a -> a #

minimum :: Ord a => RaiseStatement a -> a #

sum :: Num a => RaiseStatement a -> a #

product :: Num a => RaiseStatement a -> a #

Traversable RaiseStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> RaiseStatement a -> f (RaiseStatement b) #

sequenceA :: Applicative f => RaiseStatement (f a) -> f (RaiseStatement a) #

mapM :: Monad m => (a -> m b) -> RaiseStatement a -> m (RaiseStatement b) #

sequence :: Monad m => RaiseStatement (m a) -> m (RaiseStatement a) #

SymbolMatching RaiseStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal RaiseStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (RaiseStatement a)

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 #

Generic1 RaiseStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 RaiseStatement :: k -> Type #

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.5.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))))))
type Rep1 RaiseStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

data DeleteStatement a Source #

Constructors

DeleteStatement 

Fields

Instances
Functor DeleteStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> DeleteStatement a -> DeleteStatement b #

(<$) :: a -> DeleteStatement b -> DeleteStatement a #

Foldable DeleteStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => DeleteStatement m -> m #

foldMap :: Monoid m => (a -> m) -> DeleteStatement a -> m #

foldr :: (a -> b -> b) -> b -> DeleteStatement a -> b #

foldr' :: (a -> b -> b) -> b -> DeleteStatement a -> b #

foldl :: (b -> a -> b) -> b -> DeleteStatement a -> b #

foldl' :: (b -> a -> b) -> b -> DeleteStatement a -> b #

foldr1 :: (a -> a -> a) -> DeleteStatement a -> a #

foldl1 :: (a -> a -> a) -> DeleteStatement a -> a #

toList :: DeleteStatement a -> [a] #

null :: DeleteStatement a -> Bool #

length :: DeleteStatement a -> Int #

elem :: Eq a => a -> DeleteStatement a -> Bool #

maximum :: Ord a => DeleteStatement a -> a #

minimum :: Ord a => DeleteStatement a -> a #

sum :: Num a => DeleteStatement a -> a #

product :: Num a => DeleteStatement a -> a #

Traversable DeleteStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> DeleteStatement a -> f (DeleteStatement b) #

sequenceA :: Applicative f => DeleteStatement (f a) -> f (DeleteStatement a) #

mapM :: Monad m => (a -> m b) -> DeleteStatement a -> m (DeleteStatement b) #

sequence :: Monad m => DeleteStatement (m a) -> m (DeleteStatement a) #

SymbolMatching DeleteStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal DeleteStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (DeleteStatement a)

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 #

Generic1 DeleteStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 DeleteStatement :: k -> Type #

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.5.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))))
type Rep1 DeleteStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 DeleteStatement = D1 (MetaData "DeleteStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "DeleteStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ExpressionList)))

data Assignment a Source #

Instances
Functor Assignment Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Assignment a -> Assignment b #

(<$) :: a -> Assignment b -> Assignment a #

Foldable Assignment Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Assignment m -> m #

foldMap :: Monoid m => (a -> m) -> Assignment a -> m #

foldr :: (a -> b -> b) -> b -> Assignment a -> b #

foldr' :: (a -> b -> b) -> b -> Assignment a -> b #

foldl :: (b -> a -> b) -> b -> Assignment a -> b #

foldl' :: (b -> a -> b) -> b -> Assignment a -> b #

foldr1 :: (a -> a -> a) -> Assignment a -> a #

foldl1 :: (a -> a -> a) -> Assignment a -> a #

toList :: Assignment a -> [a] #

null :: Assignment a -> Bool #

length :: Assignment a -> Int #

elem :: Eq a => a -> Assignment a -> Bool #

maximum :: Ord a => Assignment a -> a #

minimum :: Ord a => Assignment a -> a #

sum :: Num a => Assignment a -> a #

product :: Num a => Assignment a -> a #

Traversable Assignment Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Assignment a -> f (Assignment b) #

sequenceA :: Applicative f => Assignment (f a) -> f (Assignment a) #

mapM :: Monad m => (a -> m b) -> Assignment a -> m (Assignment b) #

sequence :: Monad m => Assignment (m a) -> m (Assignment a) #

SymbolMatching Assignment Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal Assignment Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Assignment a)

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 #

Generic1 Assignment Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Assignment :: k -> Type #

type Rep (Assignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Assignment Source # 
Instance details

Defined in TreeSitter.Python.AST

data AugmentedAssignment a Source #

Instances
Functor AugmentedAssignment Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable AugmentedAssignment Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AugmentedAssignment m -> m #

foldMap :: Monoid m => (a -> m) -> AugmentedAssignment a -> m #

foldr :: (a -> b -> b) -> b -> AugmentedAssignment a -> b #

foldr' :: (a -> b -> b) -> b -> AugmentedAssignment a -> b #

foldl :: (b -> a -> b) -> b -> AugmentedAssignment a -> b #

foldl' :: (b -> a -> b) -> b -> AugmentedAssignment a -> b #

foldr1 :: (a -> a -> a) -> AugmentedAssignment a -> a #

foldl1 :: (a -> a -> a) -> AugmentedAssignment a -> a #

toList :: AugmentedAssignment a -> [a] #

null :: AugmentedAssignment a -> Bool #

length :: AugmentedAssignment a -> Int #

elem :: Eq a => a -> AugmentedAssignment a -> Bool #

maximum :: Ord a => AugmentedAssignment a -> a #

minimum :: Ord a => AugmentedAssignment a -> a #

sum :: Num a => AugmentedAssignment a -> a #

product :: Num a => AugmentedAssignment a -> a #

Traversable AugmentedAssignment Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching AugmentedAssignment Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AugmentedAssignment Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AugmentedAssignment a)

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 #

Generic1 AugmentedAssignment Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AugmentedAssignment :: k -> Type #

type Rep (AugmentedAssignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 AugmentedAssignment Source # 
Instance details

Defined in TreeSitter.Python.AST

data ExpressionStatement a Source #

Instances
Functor ExpressionStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable ExpressionStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ExpressionStatement m -> m #

foldMap :: Monoid m => (a -> m) -> ExpressionStatement a -> m #

foldr :: (a -> b -> b) -> b -> ExpressionStatement a -> b #

foldr' :: (a -> b -> b) -> b -> ExpressionStatement a -> b #

foldl :: (b -> a -> b) -> b -> ExpressionStatement a -> b #

foldl' :: (b -> a -> b) -> b -> ExpressionStatement a -> b #

foldr1 :: (a -> a -> a) -> ExpressionStatement a -> a #

foldl1 :: (a -> a -> a) -> ExpressionStatement a -> a #

toList :: ExpressionStatement a -> [a] #

null :: ExpressionStatement a -> Bool #

length :: ExpressionStatement a -> Int #

elem :: Eq a => a -> ExpressionStatement a -> Bool #

maximum :: Ord a => ExpressionStatement a -> a #

minimum :: Ord a => ExpressionStatement a -> a #

sum :: Num a => ExpressionStatement a -> a #

product :: Num a => ExpressionStatement a -> a #

Traversable ExpressionStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching ExpressionStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ExpressionStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ExpressionStatement a)

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 #

Generic1 ExpressionStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ExpressionStatement :: k -> Type #

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.5.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 ((Expression :+: (Assignment :+: (AugmentedAssignment :+: Yield))) a)))))
type Rep1 ExpressionStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ExpressionStatement = D1 (MetaData "ExpressionStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ExpressionStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 (Expression :+: (Assignment :+: (AugmentedAssignment :+: Yield))))))

data ExecStatement a Source #

Constructors

ExecStatement 

Fields

Instances
Functor ExecStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> ExecStatement a -> ExecStatement b #

(<$) :: a -> ExecStatement b -> ExecStatement a #

Foldable ExecStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ExecStatement m -> m #

foldMap :: Monoid m => (a -> m) -> ExecStatement a -> m #

foldr :: (a -> b -> b) -> b -> ExecStatement a -> b #

foldr' :: (a -> b -> b) -> b -> ExecStatement a -> b #

foldl :: (b -> a -> b) -> b -> ExecStatement a -> b #

foldl' :: (b -> a -> b) -> b -> ExecStatement a -> b #

foldr1 :: (a -> a -> a) -> ExecStatement a -> a #

foldl1 :: (a -> a -> a) -> ExecStatement a -> a #

toList :: ExecStatement a -> [a] #

null :: ExecStatement a -> Bool #

length :: ExecStatement a -> Int #

elem :: Eq a => a -> ExecStatement a -> Bool #

maximum :: Ord a => ExecStatement a -> a #

minimum :: Ord a => ExecStatement a -> a #

sum :: Num a => ExecStatement a -> a #

product :: Num a => ExecStatement a -> a #

Traversable ExecStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ExecStatement a -> f (ExecStatement b) #

sequenceA :: Applicative f => ExecStatement (f a) -> f (ExecStatement a) #

mapM :: Monad m => (a -> m b) -> ExecStatement a -> m (ExecStatement b) #

sequence :: Monad m => ExecStatement (m a) -> m (ExecStatement a) #

SymbolMatching ExecStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ExecStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ExecStatement a)

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 #

Generic1 ExecStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ExecStatement :: k -> Type #

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.5.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]))))
type Rep1 ExecStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ExecStatement = D1 (MetaData "ExecStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ExecStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: (S1 (MetaSel (Just "code") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 String) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 Expression))))

data Parameters a Source #

Constructors

Parameters 

Fields

Instances
Functor Parameters Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Parameters a -> Parameters b #

(<$) :: a -> Parameters b -> Parameters a #

Foldable Parameters Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Parameters m -> m #

foldMap :: Monoid m => (a -> m) -> Parameters a -> m #

foldr :: (a -> b -> b) -> b -> Parameters a -> b #

foldr' :: (a -> b -> b) -> b -> Parameters a -> b #

foldl :: (b -> a -> b) -> b -> Parameters a -> b #

foldl' :: (b -> a -> b) -> b -> Parameters a -> b #

foldr1 :: (a -> a -> a) -> Parameters a -> a #

foldl1 :: (a -> a -> a) -> Parameters a -> a #

toList :: Parameters a -> [a] #

null :: Parameters a -> Bool #

length :: Parameters a -> Int #

elem :: Eq a => a -> Parameters a -> Bool #

maximum :: Ord a => Parameters a -> a #

minimum :: Ord a => Parameters a -> a #

sum :: Num a => Parameters a -> a #

product :: Num a => Parameters a -> a #

Traversable Parameters Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Parameters a -> f (Parameters b) #

sequenceA :: Applicative f => Parameters (f a) -> f (Parameters a) #

mapM :: Monad m => (a -> m b) -> Parameters a -> m (Parameters b) #

sequence :: Monad m => Parameters (m a) -> m (Parameters a) #

SymbolMatching Parameters Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal Parameters Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Parameters a)

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 #

Generic1 Parameters Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Parameters :: k -> Type #

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.5.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])))
type Rep1 Parameters Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Parameters = D1 (MetaData "Parameters" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Parameters" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 Parameter)))

data Chevron a Source #

Constructors

Chevron 

Fields

Instances
Functor Chevron Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Chevron a -> Chevron b #

(<$) :: a -> Chevron b -> Chevron a #

Foldable Chevron Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Chevron m -> m #

foldMap :: Monoid m => (a -> m) -> Chevron a -> m #

foldr :: (a -> b -> b) -> b -> Chevron a -> b #

foldr' :: (a -> b -> b) -> b -> Chevron a -> b #

foldl :: (b -> a -> b) -> b -> Chevron a -> b #

foldl' :: (b -> a -> b) -> b -> Chevron a -> b #

foldr1 :: (a -> a -> a) -> Chevron a -> a #

foldl1 :: (a -> a -> a) -> Chevron a -> a #

toList :: Chevron a -> [a] #

null :: Chevron a -> Bool #

length :: Chevron a -> Int #

elem :: Eq a => a -> Chevron a -> Bool #

maximum :: Ord a => Chevron a -> a #

minimum :: Ord a => Chevron a -> a #

sum :: Num a => Chevron a -> a #

product :: Num a => Chevron a -> a #

Traversable Chevron Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Chevron a -> f (Chevron b) #

sequenceA :: Applicative f => Chevron (f a) -> f (Chevron a) #

mapM :: Monad m => (a -> m b) -> Chevron a -> m (Chevron b) #

sequence :: Monad m => Chevron (m a) -> m (Chevron a) #

SymbolMatching Chevron Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Chevron -> Node -> Bool

showFailure :: Proxy Chevron -> Node -> String

Unmarshal Chevron Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Chevron a)

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 #

Generic1 Chevron Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Chevron :: k -> Type #

Methods

from1 :: Chevron a -> Rep1 Chevron a #

to1 :: Rep1 Chevron a -> Chevron a #

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.5.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))))
type Rep1 Chevron Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Chevron = D1 (MetaData "Chevron" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Chevron" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Expression)))

data PrintStatement a Source #

Constructors

PrintStatement 

Fields

Instances
Functor PrintStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> PrintStatement a -> PrintStatement b #

(<$) :: a -> PrintStatement b -> PrintStatement a #

Foldable PrintStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => PrintStatement m -> m #

foldMap :: Monoid m => (a -> m) -> PrintStatement a -> m #

foldr :: (a -> b -> b) -> b -> PrintStatement a -> b #

foldr' :: (a -> b -> b) -> b -> PrintStatement a -> b #

foldl :: (b -> a -> b) -> b -> PrintStatement a -> b #

foldl' :: (b -> a -> b) -> b -> PrintStatement a -> b #

foldr1 :: (a -> a -> a) -> PrintStatement a -> a #

foldl1 :: (a -> a -> a) -> PrintStatement a -> a #

toList :: PrintStatement a -> [a] #

null :: PrintStatement a -> Bool #

length :: PrintStatement a -> Int #

elem :: Eq a => a -> PrintStatement a -> Bool #

maximum :: Ord a => PrintStatement a -> a #

minimum :: Ord a => PrintStatement a -> a #

sum :: Num a => PrintStatement a -> a #

product :: Num a => PrintStatement a -> a #

Traversable PrintStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> PrintStatement a -> f (PrintStatement b) #

sequenceA :: Applicative f => PrintStatement (f a) -> f (PrintStatement a) #

mapM :: Monad m => (a -> m b) -> PrintStatement a -> m (PrintStatement b) #

sequence :: Monad m => PrintStatement (m a) -> m (PrintStatement a) #

SymbolMatching PrintStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal PrintStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (PrintStatement a)

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 #

Generic1 PrintStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 PrintStatement :: k -> Type #

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.5.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]))))
type Rep1 PrintStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 PrintStatement = D1 (MetaData "PrintStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "PrintStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: (S1 (MetaSel (Just "argument") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 Expression) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 Chevron))))

data AssertStatement a Source #

Constructors

AssertStatement 

Fields

Instances
Functor AssertStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AssertStatement a -> AssertStatement b #

(<$) :: a -> AssertStatement b -> AssertStatement a #

Foldable AssertStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AssertStatement m -> m #

foldMap :: Monoid m => (a -> m) -> AssertStatement a -> m #

foldr :: (a -> b -> b) -> b -> AssertStatement a -> b #

foldr' :: (a -> b -> b) -> b -> AssertStatement a -> b #

foldl :: (b -> a -> b) -> b -> AssertStatement a -> b #

foldl' :: (b -> a -> b) -> b -> AssertStatement a -> b #

foldr1 :: (a -> a -> a) -> AssertStatement a -> a #

foldl1 :: (a -> a -> a) -> AssertStatement a -> a #

toList :: AssertStatement a -> [a] #

null :: AssertStatement a -> Bool #

length :: AssertStatement a -> Int #

elem :: Eq a => a -> AssertStatement a -> Bool #

maximum :: Ord a => AssertStatement a -> a #

minimum :: Ord a => AssertStatement a -> a #

sum :: Num a => AssertStatement a -> a #

product :: Num a => AssertStatement a -> a #

Traversable AssertStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AssertStatement a -> f (AssertStatement b) #

sequenceA :: Applicative f => AssertStatement (f a) -> f (AssertStatement a) #

mapM :: Monad m => (a -> m b) -> AssertStatement a -> m (AssertStatement b) #

sequence :: Monad m => AssertStatement (m a) -> m (AssertStatement a) #

SymbolMatching AssertStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AssertStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AssertStatement a)

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 #

Generic1 AssertStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AssertStatement :: k -> Type #

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.5.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)))))
type Rep1 AssertStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 AssertStatement = D1 (MetaData "AssertStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "AssertStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 Expression)))

data SimpleStatement a Source #

Instances
Functor SimpleStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> SimpleStatement a -> SimpleStatement b #

(<$) :: a -> SimpleStatement b -> SimpleStatement a #

Foldable SimpleStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => SimpleStatement m -> m #

foldMap :: Monoid m => (a -> m) -> SimpleStatement a -> m #

foldr :: (a -> b -> b) -> b -> SimpleStatement a -> b #

foldr' :: (a -> b -> b) -> b -> SimpleStatement a -> b #

foldl :: (b -> a -> b) -> b -> SimpleStatement a -> b #

foldl' :: (b -> a -> b) -> b -> SimpleStatement a -> b #

foldr1 :: (a -> a -> a) -> SimpleStatement a -> a #

foldl1 :: (a -> a -> a) -> SimpleStatement a -> a #

toList :: SimpleStatement a -> [a] #

null :: SimpleStatement a -> Bool #

length :: SimpleStatement a -> Int #

elem :: Eq a => a -> SimpleStatement a -> Bool #

maximum :: Ord a => SimpleStatement a -> a #

minimum :: Ord a => SimpleStatement a -> a #

sum :: Num a => SimpleStatement a -> a #

product :: Num a => SimpleStatement a -> a #

Traversable SimpleStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> SimpleStatement a -> f (SimpleStatement b) #

sequenceA :: Applicative f => SimpleStatement (f a) -> f (SimpleStatement a) #

mapM :: Monad m => (a -> m b) -> SimpleStatement a -> m (SimpleStatement b) #

sequence :: Monad m => SimpleStatement (m a) -> m (SimpleStatement a) #

SymbolMatching SimpleStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal SimpleStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (SimpleStatement a)

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 #

Generic1 SimpleStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 SimpleStatement :: k -> Type #

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.5.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)))))))
type Rep1 SimpleStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 SimpleStatement = D1 (MetaData "SimpleStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (((C1 (MetaCons "AssertStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 AssertStatement)) :+: (C1 (MetaCons "BreakStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 BreakStatement)) :+: C1 (MetaCons "ContinueStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ContinueStatement)))) :+: ((C1 (MetaCons "DeleteStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 DeleteStatement)) :+: C1 (MetaCons "ExecStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ExecStatement))) :+: (C1 (MetaCons "ExpressionStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ExpressionStatement)) :+: C1 (MetaCons "FutureImportStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 FutureImportStatement))))) :+: (((C1 (MetaCons "GlobalStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 GlobalStatement)) :+: C1 (MetaCons "ImportFromStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ImportFromStatement))) :+: (C1 (MetaCons "ImportStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ImportStatement)) :+: C1 (MetaCons "NonlocalStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 NonlocalStatement)))) :+: ((C1 (MetaCons "PassStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 PassStatement)) :+: C1 (MetaCons "PrintStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 PrintStatement))) :+: (C1 (MetaCons "RaiseStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 RaiseStatement)) :+: C1 (MetaCons "ReturnStatementSimpleStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ReturnStatement))))))

data Decorator a Source #

Constructors

Decorator 

Fields

Instances
Functor Decorator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Decorator a -> Decorator b #

(<$) :: a -> Decorator b -> Decorator a #

Foldable Decorator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Decorator m -> m #

foldMap :: Monoid m => (a -> m) -> Decorator a -> m #

foldr :: (a -> b -> b) -> b -> Decorator a -> b #

foldr' :: (a -> b -> b) -> b -> Decorator a -> b #

foldl :: (b -> a -> b) -> b -> Decorator a -> b #

foldl' :: (b -> a -> b) -> b -> Decorator a -> b #

foldr1 :: (a -> a -> a) -> Decorator a -> a #

foldl1 :: (a -> a -> a) -> Decorator a -> a #

toList :: Decorator a -> [a] #

null :: Decorator a -> Bool #

length :: Decorator a -> Int #

elem :: Eq a => a -> Decorator a -> Bool #

maximum :: Ord a => Decorator a -> a #

minimum :: Ord a => Decorator a -> a #

sum :: Num a => Decorator a -> a #

product :: Num a => Decorator a -> a #

Traversable Decorator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Decorator a -> f (Decorator b) #

sequenceA :: Applicative f => Decorator (f a) -> f (Decorator a) #

mapM :: Monad m => (a -> m b) -> Decorator a -> m (Decorator b) #

sequence :: Monad m => Decorator (m a) -> m (Decorator a) #

SymbolMatching Decorator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Decorator -> Node -> Bool

showFailure :: Proxy Decorator -> Node -> String

Unmarshal Decorator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Decorator a)

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 #

Generic1 Decorator Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Decorator :: k -> Type #

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.5.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)))))
type Rep1 Decorator Source # 
Instance details

Defined in TreeSitter.Python.AST

data ClassDefinition a Source #

Constructors

ClassDefinition 

Fields

Instances
Functor ClassDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> ClassDefinition a -> ClassDefinition b #

(<$) :: a -> ClassDefinition b -> ClassDefinition a #

Foldable ClassDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ClassDefinition m -> m #

foldMap :: Monoid m => (a -> m) -> ClassDefinition a -> m #

foldr :: (a -> b -> b) -> b -> ClassDefinition a -> b #

foldr' :: (a -> b -> b) -> b -> ClassDefinition a -> b #

foldl :: (b -> a -> b) -> b -> ClassDefinition a -> b #

foldl' :: (b -> a -> b) -> b -> ClassDefinition a -> b #

foldr1 :: (a -> a -> a) -> ClassDefinition a -> a #

foldl1 :: (a -> a -> a) -> ClassDefinition a -> a #

toList :: ClassDefinition a -> [a] #

null :: ClassDefinition a -> Bool #

length :: ClassDefinition a -> Int #

elem :: Eq a => a -> ClassDefinition a -> Bool #

maximum :: Ord a => ClassDefinition a -> a #

minimum :: Ord a => ClassDefinition a -> a #

sum :: Num a => ClassDefinition a -> a #

product :: Num a => ClassDefinition a -> a #

Traversable ClassDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ClassDefinition a -> f (ClassDefinition b) #

sequenceA :: Applicative f => ClassDefinition (f a) -> f (ClassDefinition a) #

mapM :: Monad m => (a -> m b) -> ClassDefinition a -> m (ClassDefinition b) #

sequence :: Monad m => ClassDefinition (m a) -> m (ClassDefinition a) #

SymbolMatching ClassDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ClassDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ClassDefinition a)

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 #

Generic1 ClassDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ClassDefinition :: k -> Type #

type Rep (ClassDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ClassDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

data Block a Source #

Constructors

Block 
Instances
Functor Block Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Block a -> Block b #

(<$) :: a -> Block b -> Block a #

Foldable Block Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Block m -> m #

foldMap :: Monoid m => (a -> m) -> Block a -> m #

foldr :: (a -> b -> b) -> b -> Block a -> b #

foldr' :: (a -> b -> b) -> b -> Block a -> b #

foldl :: (b -> a -> b) -> b -> Block a -> b #

foldl' :: (b -> a -> b) -> b -> Block a -> b #

foldr1 :: (a -> a -> a) -> Block a -> a #

foldl1 :: (a -> a -> a) -> Block a -> a #

toList :: Block a -> [a] #

null :: Block a -> Bool #

length :: Block a -> Int #

elem :: Eq a => a -> Block a -> Bool #

maximum :: Ord a => Block a -> a #

minimum :: Ord a => Block a -> a #

sum :: Num a => Block a -> a #

product :: Num a => Block a -> a #

Traversable Block Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Block a -> f (Block b) #

sequenceA :: Applicative f => Block (f a) -> f (Block a) #

mapM :: Monad m => (a -> m b) -> Block a -> m (Block b) #

sequence :: Monad m => Block (m a) -> m (Block a) #

SymbolMatching Block Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Block -> Node -> Bool

showFailure :: Proxy Block -> Node -> String

Unmarshal Block Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Block a)

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 #

Generic1 Block Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Block :: k -> Type #

Methods

from1 :: Block a -> Rep1 Block a #

to1 :: Rep1 Block a -> Block a #

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.5.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 [(CompoundStatement :+: SimpleStatement) a])))
type Rep1 Block Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Block = D1 (MetaData "Block" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Block" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 (CompoundStatement :+: SimpleStatement))))

data CompoundStatement a Source #

Instances
Functor CompoundStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable CompoundStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => CompoundStatement m -> m #

foldMap :: Monoid m => (a -> m) -> CompoundStatement a -> m #

foldr :: (a -> b -> b) -> b -> CompoundStatement a -> b #

foldr' :: (a -> b -> b) -> b -> CompoundStatement a -> b #

foldl :: (b -> a -> b) -> b -> CompoundStatement a -> b #

foldl' :: (b -> a -> b) -> b -> CompoundStatement a -> b #

foldr1 :: (a -> a -> a) -> CompoundStatement a -> a #

foldl1 :: (a -> a -> a) -> CompoundStatement a -> a #

toList :: CompoundStatement a -> [a] #

null :: CompoundStatement a -> Bool #

length :: CompoundStatement a -> Int #

elem :: Eq a => a -> CompoundStatement a -> Bool #

maximum :: Ord a => CompoundStatement a -> a #

minimum :: Ord a => CompoundStatement a -> a #

sum :: Num a => CompoundStatement a -> a #

product :: Num a => CompoundStatement a -> a #

Traversable CompoundStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> CompoundStatement a -> f (CompoundStatement b) #

sequenceA :: Applicative f => CompoundStatement (f a) -> f (CompoundStatement a) #

mapM :: Monad m => (a -> m b) -> CompoundStatement a -> m (CompoundStatement b) #

sequence :: Monad m => CompoundStatement (m a) -> m (CompoundStatement a) #

SymbolMatching CompoundStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal CompoundStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (CompoundStatement a)

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 #

Generic1 CompoundStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 CompoundStatement :: k -> Type #

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.5.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))))))
type Rep1 CompoundStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 CompoundStatement = D1 (MetaData "CompoundStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (((C1 (MetaCons "ClassDefinitionCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ClassDefinition)) :+: C1 (MetaCons "DecoratedDefinitionCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 DecoratedDefinition))) :+: (C1 (MetaCons "ForStatementCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ForStatement)) :+: C1 (MetaCons "FunctionDefinitionCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 FunctionDefinition)))) :+: ((C1 (MetaCons "IfStatementCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 IfStatement)) :+: C1 (MetaCons "TryStatementCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 TryStatement))) :+: (C1 (MetaCons "WhileStatementCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 WhileStatement)) :+: C1 (MetaCons "WithStatementCompoundStatement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 WithStatement)))))

data WithStatement a Source #

Constructors

WithStatement 

Fields

Instances
Functor WithStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> WithStatement a -> WithStatement b #

(<$) :: a -> WithStatement b -> WithStatement a #

Foldable WithStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => WithStatement m -> m #

foldMap :: Monoid m => (a -> m) -> WithStatement a -> m #

foldr :: (a -> b -> b) -> b -> WithStatement a -> b #

foldr' :: (a -> b -> b) -> b -> WithStatement a -> b #

foldl :: (b -> a -> b) -> b -> WithStatement a -> b #

foldl' :: (b -> a -> b) -> b -> WithStatement a -> b #

foldr1 :: (a -> a -> a) -> WithStatement a -> a #

foldl1 :: (a -> a -> a) -> WithStatement a -> a #

toList :: WithStatement a -> [a] #

null :: WithStatement a -> Bool #

length :: WithStatement a -> Int #

elem :: Eq a => a -> WithStatement a -> Bool #

maximum :: Ord a => WithStatement a -> a #

minimum :: Ord a => WithStatement a -> a #

sum :: Num a => WithStatement a -> a #

product :: Num a => WithStatement a -> a #

Traversable WithStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> WithStatement a -> f (WithStatement b) #

sequenceA :: Applicative f => WithStatement (f a) -> f (WithStatement a) #

mapM :: Monad m => (a -> m b) -> WithStatement a -> m (WithStatement b) #

sequence :: Monad m => WithStatement (m a) -> m (WithStatement a) #

SymbolMatching WithStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal WithStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (WithStatement a)

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 #

Generic1 WithStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 WithStatement :: k -> Type #

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.5.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))))))
type Rep1 WithStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 WithStatement = D1 (MetaData "WithStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "WithStatement" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: (S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Block) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 WithItem))))

data WhileStatement a Source #

Constructors

WhileStatement 

Fields

Instances
Functor WhileStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> WhileStatement a -> WhileStatement b #

(<$) :: a -> WhileStatement b -> WhileStatement a #

Foldable WhileStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => WhileStatement m -> m #

foldMap :: Monoid m => (a -> m) -> WhileStatement a -> m #

foldr :: (a -> b -> b) -> b -> WhileStatement a -> b #

foldr' :: (a -> b -> b) -> b -> WhileStatement a -> b #

foldl :: (b -> a -> b) -> b -> WhileStatement a -> b #

foldl' :: (b -> a -> b) -> b -> WhileStatement a -> b #

foldr1 :: (a -> a -> a) -> WhileStatement a -> a #

foldl1 :: (a -> a -> a) -> WhileStatement a -> a #

toList :: WhileStatement a -> [a] #

null :: WhileStatement a -> Bool #

length :: WhileStatement a -> Int #

elem :: Eq a => a -> WhileStatement a -> Bool #

maximum :: Ord a => WhileStatement a -> a #

minimum :: Ord a => WhileStatement a -> a #

sum :: Num a => WhileStatement a -> a #

product :: Num a => WhileStatement a -> a #

Traversable WhileStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> WhileStatement a -> f (WhileStatement b) #

sequenceA :: Applicative f => WhileStatement (f a) -> f (WhileStatement a) #

mapM :: Monad m => (a -> m b) -> WhileStatement a -> m (WhileStatement b) #

sequence :: Monad m => WhileStatement (m a) -> m (WhileStatement a) #

SymbolMatching WhileStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal WhileStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (WhileStatement a)

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 #

Generic1 WhileStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 WhileStatement :: k -> Type #

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.5.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)))))
type Rep1 WhileStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

data ElseClause a Source #

Constructors

ElseClause 

Fields

Instances
Functor ElseClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> ElseClause a -> ElseClause b #

(<$) :: a -> ElseClause b -> ElseClause a #

Foldable ElseClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ElseClause m -> m #

foldMap :: Monoid m => (a -> m) -> ElseClause a -> m #

foldr :: (a -> b -> b) -> b -> ElseClause a -> b #

foldr' :: (a -> b -> b) -> b -> ElseClause a -> b #

foldl :: (b -> a -> b) -> b -> ElseClause a -> b #

foldl' :: (b -> a -> b) -> b -> ElseClause a -> b #

foldr1 :: (a -> a -> a) -> ElseClause a -> a #

foldl1 :: (a -> a -> a) -> ElseClause a -> a #

toList :: ElseClause a -> [a] #

null :: ElseClause a -> Bool #

length :: ElseClause a -> Int #

elem :: Eq a => a -> ElseClause a -> Bool #

maximum :: Ord a => ElseClause a -> a #

minimum :: Ord a => ElseClause a -> a #

sum :: Num a => ElseClause a -> a #

product :: Num a => ElseClause a -> a #

Traversable ElseClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ElseClause a -> f (ElseClause b) #

sequenceA :: Applicative f => ElseClause (f a) -> f (ElseClause a) #

mapM :: Monad m => (a -> m b) -> ElseClause a -> m (ElseClause b) #

sequence :: Monad m => ElseClause (m a) -> m (ElseClause a) #

SymbolMatching ElseClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ElseClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ElseClause a)

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 #

Generic1 ElseClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ElseClause :: k -> Type #

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.5.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))))
type Rep1 ElseClause Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ElseClause = D1 (MetaData "ElseClause" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ElseClause" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Block)))

data TryStatement a Source #

Instances
Functor TryStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> TryStatement a -> TryStatement b #

(<$) :: a -> TryStatement b -> TryStatement a #

Foldable TryStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => TryStatement m -> m #

foldMap :: Monoid m => (a -> m) -> TryStatement a -> m #

foldr :: (a -> b -> b) -> b -> TryStatement a -> b #

foldr' :: (a -> b -> b) -> b -> TryStatement a -> b #

foldl :: (b -> a -> b) -> b -> TryStatement a -> b #

foldl' :: (b -> a -> b) -> b -> TryStatement a -> b #

foldr1 :: (a -> a -> a) -> TryStatement a -> a #

foldl1 :: (a -> a -> a) -> TryStatement a -> a #

toList :: TryStatement a -> [a] #

null :: TryStatement a -> Bool #

length :: TryStatement a -> Int #

elem :: Eq a => a -> TryStatement a -> Bool #

maximum :: Ord a => TryStatement a -> a #

minimum :: Ord a => TryStatement a -> a #

sum :: Num a => TryStatement a -> a #

product :: Num a => TryStatement a -> a #

Traversable TryStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> TryStatement a -> f (TryStatement b) #

sequenceA :: Applicative f => TryStatement (f a) -> f (TryStatement a) #

mapM :: Monad m => (a -> m b) -> TryStatement a -> m (TryStatement b) #

sequence :: Monad m => TryStatement (m a) -> m (TryStatement a) #

SymbolMatching TryStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal TryStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (TryStatement a)

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 #

Generic1 TryStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 TryStatement :: k -> Type #

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.5.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 ((ElseClause :+: (ExceptClause :+: FinallyClause)) a))))))
type Rep1 TryStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

data FinallyClause a Source #

Constructors

FinallyClause 

Fields

Instances
Functor FinallyClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> FinallyClause a -> FinallyClause b #

(<$) :: a -> FinallyClause b -> FinallyClause a #

Foldable FinallyClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => FinallyClause m -> m #

foldMap :: Monoid m => (a -> m) -> FinallyClause a -> m #

foldr :: (a -> b -> b) -> b -> FinallyClause a -> b #

foldr' :: (a -> b -> b) -> b -> FinallyClause a -> b #

foldl :: (b -> a -> b) -> b -> FinallyClause a -> b #

foldl' :: (b -> a -> b) -> b -> FinallyClause a -> b #

foldr1 :: (a -> a -> a) -> FinallyClause a -> a #

foldl1 :: (a -> a -> a) -> FinallyClause a -> a #

toList :: FinallyClause a -> [a] #

null :: FinallyClause a -> Bool #

length :: FinallyClause a -> Int #

elem :: Eq a => a -> FinallyClause a -> Bool #

maximum :: Ord a => FinallyClause a -> a #

minimum :: Ord a => FinallyClause a -> a #

sum :: Num a => FinallyClause a -> a #

product :: Num a => FinallyClause a -> a #

Traversable FinallyClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> FinallyClause a -> f (FinallyClause b) #

sequenceA :: Applicative f => FinallyClause (f a) -> f (FinallyClause a) #

mapM :: Monad m => (a -> m b) -> FinallyClause a -> m (FinallyClause b) #

sequence :: Monad m => FinallyClause (m a) -> m (FinallyClause a) #

SymbolMatching FinallyClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal FinallyClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (FinallyClause a)

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 #

Generic1 FinallyClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 FinallyClause :: k -> Type #

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.5.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))))
type Rep1 FinallyClause Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 FinallyClause = D1 (MetaData "FinallyClause" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "FinallyClause" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Block)))

data ExceptClause a Source #

Constructors

ExceptClause 
Instances
Functor ExceptClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> ExceptClause a -> ExceptClause b #

(<$) :: a -> ExceptClause b -> ExceptClause a #

Foldable ExceptClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ExceptClause m -> m #

foldMap :: Monoid m => (a -> m) -> ExceptClause a -> m #

foldr :: (a -> b -> b) -> b -> ExceptClause a -> b #

foldr' :: (a -> b -> b) -> b -> ExceptClause a -> b #

foldl :: (b -> a -> b) -> b -> ExceptClause a -> b #

foldl' :: (b -> a -> b) -> b -> ExceptClause a -> b #

foldr1 :: (a -> a -> a) -> ExceptClause a -> a #

foldl1 :: (a -> a -> a) -> ExceptClause a -> a #

toList :: ExceptClause a -> [a] #

null :: ExceptClause a -> Bool #

length :: ExceptClause a -> Int #

elem :: Eq a => a -> ExceptClause a -> Bool #

maximum :: Ord a => ExceptClause a -> a #

minimum :: Ord a => ExceptClause a -> a #

sum :: Num a => ExceptClause a -> a #

product :: Num a => ExceptClause a -> a #

Traversable ExceptClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ExceptClause a -> f (ExceptClause b) #

sequenceA :: Applicative f => ExceptClause (f a) -> f (ExceptClause a) #

mapM :: Monad m => (a -> m b) -> ExceptClause a -> m (ExceptClause b) #

sequence :: Monad m => ExceptClause (m a) -> m (ExceptClause a) #

SymbolMatching ExceptClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ExceptClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ExceptClause a)

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 #

Generic1 ExceptClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ExceptClause :: k -> Type #

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.5.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 ((Expression :+: Block) a)))))
type Rep1 ExceptClause Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ExceptClause = D1 (MetaData "ExceptClause" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ExceptClause" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (NonEmpty :.: Rec1 (Expression :+: Block))))

data IfStatement a Source #

Constructors

IfStatement 

Fields

Instances
Functor IfStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> IfStatement a -> IfStatement b #

(<$) :: a -> IfStatement b -> IfStatement a #

Foldable IfStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => IfStatement m -> m #

foldMap :: Monoid m => (a -> m) -> IfStatement a -> m #

foldr :: (a -> b -> b) -> b -> IfStatement a -> b #

foldr' :: (a -> b -> b) -> b -> IfStatement a -> b #

foldl :: (b -> a -> b) -> b -> IfStatement a -> b #

foldl' :: (b -> a -> b) -> b -> IfStatement a -> b #

foldr1 :: (a -> a -> a) -> IfStatement a -> a #

foldl1 :: (a -> a -> a) -> IfStatement a -> a #

toList :: IfStatement a -> [a] #

null :: IfStatement a -> Bool #

length :: IfStatement a -> Int #

elem :: Eq a => a -> IfStatement a -> Bool #

maximum :: Ord a => IfStatement a -> a #

minimum :: Ord a => IfStatement a -> a #

sum :: Num a => IfStatement a -> a #

product :: Num a => IfStatement a -> a #

Traversable IfStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> IfStatement a -> f (IfStatement b) #

sequenceA :: Applicative f => IfStatement (f a) -> f (IfStatement a) #

mapM :: Monad m => (a -> m b) -> IfStatement a -> m (IfStatement b) #

sequence :: Monad m => IfStatement (m a) -> m (IfStatement a) #

SymbolMatching IfStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal IfStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (IfStatement a)

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 #

Generic1 IfStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 IfStatement :: k -> Type #

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.5.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 [(ElifClause :+: ElseClause) a])) :*: (S1 (MetaSel (Just "consequence") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Block a)) :*: S1 (MetaSel (Just "condition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expression a)))))
type Rep1 IfStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

data ElifClause a Source #

Constructors

ElifClause 

Fields

Instances
Functor ElifClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> ElifClause a -> ElifClause b #

(<$) :: a -> ElifClause b -> ElifClause a #

Foldable ElifClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ElifClause m -> m #

foldMap :: Monoid m => (a -> m) -> ElifClause a -> m #

foldr :: (a -> b -> b) -> b -> ElifClause a -> b #

foldr' :: (a -> b -> b) -> b -> ElifClause a -> b #

foldl :: (b -> a -> b) -> b -> ElifClause a -> b #

foldl' :: (b -> a -> b) -> b -> ElifClause a -> b #

foldr1 :: (a -> a -> a) -> ElifClause a -> a #

foldl1 :: (a -> a -> a) -> ElifClause a -> a #

toList :: ElifClause a -> [a] #

null :: ElifClause a -> Bool #

length :: ElifClause a -> Int #

elem :: Eq a => a -> ElifClause a -> Bool #

maximum :: Ord a => ElifClause a -> a #

minimum :: Ord a => ElifClause a -> a #

sum :: Num a => ElifClause a -> a #

product :: Num a => ElifClause a -> a #

Traversable ElifClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ElifClause a -> f (ElifClause b) #

sequenceA :: Applicative f => ElifClause (f a) -> f (ElifClause a) #

mapM :: Monad m => (a -> m b) -> ElifClause a -> m (ElifClause b) #

sequence :: Monad m => ElifClause (m a) -> m (ElifClause a) #

SymbolMatching ElifClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ElifClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ElifClause a)

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 #

Generic1 ElifClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ElifClause :: k -> Type #

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.5.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)))))
type Rep1 ElifClause Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ElifClause = D1 (MetaData "ElifClause" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "ElifClause" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: (S1 (MetaSel (Just "consequence") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Block) :*: S1 (MetaSel (Just "condition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Expression))))

data FunctionDefinition a Source #

Constructors

FunctionDefinition 

Fields

Instances
Functor FunctionDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable FunctionDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => FunctionDefinition m -> m #

foldMap :: Monoid m => (a -> m) -> FunctionDefinition a -> m #

foldr :: (a -> b -> b) -> b -> FunctionDefinition a -> b #

foldr' :: (a -> b -> b) -> b -> FunctionDefinition a -> b #

foldl :: (b -> a -> b) -> b -> FunctionDefinition a -> b #

foldl' :: (b -> a -> b) -> b -> FunctionDefinition a -> b #

foldr1 :: (a -> a -> a) -> FunctionDefinition a -> a #

foldl1 :: (a -> a -> a) -> FunctionDefinition a -> a #

toList :: FunctionDefinition a -> [a] #

null :: FunctionDefinition a -> Bool #

length :: FunctionDefinition a -> Int #

elem :: Eq a => a -> FunctionDefinition a -> Bool #

maximum :: Ord a => FunctionDefinition a -> a #

minimum :: Ord a => FunctionDefinition a -> a #

sum :: Num a => FunctionDefinition a -> a #

product :: Num a => FunctionDefinition a -> a #

Traversable FunctionDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching FunctionDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal FunctionDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (FunctionDefinition a)

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 #

Generic1 FunctionDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 FunctionDefinition :: k -> Type #

type Rep (FunctionDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 FunctionDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

data ForStatement a Source #

Constructors

ForStatement 

Fields

Instances
Functor ForStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> ForStatement a -> ForStatement b #

(<$) :: a -> ForStatement b -> ForStatement a #

Foldable ForStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => ForStatement m -> m #

foldMap :: Monoid m => (a -> m) -> ForStatement a -> m #

foldr :: (a -> b -> b) -> b -> ForStatement a -> b #

foldr' :: (a -> b -> b) -> b -> ForStatement a -> b #

foldl :: (b -> a -> b) -> b -> ForStatement a -> b #

foldl' :: (b -> a -> b) -> b -> ForStatement a -> b #

foldr1 :: (a -> a -> a) -> ForStatement a -> a #

foldl1 :: (a -> a -> a) -> ForStatement a -> a #

toList :: ForStatement a -> [a] #

null :: ForStatement a -> Bool #

length :: ForStatement a -> Int #

elem :: Eq a => a -> ForStatement a -> Bool #

maximum :: Ord a => ForStatement a -> a #

minimum :: Ord a => ForStatement a -> a #

sum :: Num a => ForStatement a -> a #

product :: Num a => ForStatement a -> a #

Traversable ForStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> ForStatement a -> f (ForStatement b) #

sequenceA :: Applicative f => ForStatement (f a) -> f (ForStatement a) #

mapM :: Monad m => (a -> m b) -> ForStatement a -> m (ForStatement b) #

sequence :: Monad m => ForStatement (m a) -> m (ForStatement a) #

SymbolMatching ForStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal ForStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (ForStatement a)

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 #

Generic1 ForStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 ForStatement :: k -> Type #

type Rep (ForStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ForStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

data DecoratedDefinition a Source #

Instances
Functor DecoratedDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Foldable DecoratedDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => DecoratedDefinition m -> m #

foldMap :: Monoid m => (a -> m) -> DecoratedDefinition a -> m #

foldr :: (a -> b -> b) -> b -> DecoratedDefinition a -> b #

foldr' :: (a -> b -> b) -> b -> DecoratedDefinition a -> b #

foldl :: (b -> a -> b) -> b -> DecoratedDefinition a -> b #

foldl' :: (b -> a -> b) -> b -> DecoratedDefinition a -> b #

foldr1 :: (a -> a -> a) -> DecoratedDefinition a -> a #

foldl1 :: (a -> a -> a) -> DecoratedDefinition a -> a #

toList :: DecoratedDefinition a -> [a] #

null :: DecoratedDefinition a -> Bool #

length :: DecoratedDefinition a -> Int #

elem :: Eq a => a -> DecoratedDefinition a -> Bool #

maximum :: Ord a => DecoratedDefinition a -> a #

minimum :: Ord a => DecoratedDefinition a -> a #

sum :: Num a => DecoratedDefinition a -> a #

product :: Num a => DecoratedDefinition a -> a #

Traversable DecoratedDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

SymbolMatching DecoratedDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal DecoratedDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (DecoratedDefinition a)

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 #

Generic1 DecoratedDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 DecoratedDefinition :: k -> Type #

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.5.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 ((ClassDefinition :+: FunctionDefinition) a)) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Decorator a))))))
type Rep1 DecoratedDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

data Module a Source #

Constructors

Module 
Instances
Functor Module Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Module a -> Module b #

(<$) :: a -> Module b -> Module a #

Foldable Module Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Module m -> m #

foldMap :: Monoid m => (a -> m) -> Module a -> m #

foldr :: (a -> b -> b) -> b -> Module a -> b #

foldr' :: (a -> b -> b) -> b -> Module a -> b #

foldl :: (b -> a -> b) -> b -> Module a -> b #

foldl' :: (b -> a -> b) -> b -> Module a -> b #

foldr1 :: (a -> a -> a) -> Module a -> a #

foldl1 :: (a -> a -> a) -> Module a -> a #

toList :: Module a -> [a] #

null :: Module a -> Bool #

length :: Module a -> Int #

elem :: Eq a => a -> Module a -> Bool #

maximum :: Ord a => Module a -> a #

minimum :: Ord a => Module a -> a #

sum :: Num a => Module a -> a #

product :: Num a => Module a -> a #

Traversable Module Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Module a -> f (Module b) #

sequenceA :: Applicative f => Module (f a) -> f (Module a) #

mapM :: Monad m => (a -> m b) -> Module a -> m (Module b) #

sequence :: Monad m => Module (m a) -> m (Module a) #

SymbolMatching Module Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Module -> Node -> Bool

showFailure :: Proxy Module -> Node -> String

Unmarshal Module Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Module a)

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 #

Generic1 Module Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Module :: k -> Type #

Methods

from1 :: Module a -> Rep1 Module a #

to1 :: Rep1 Module a -> Module a #

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.5.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 [(CompoundStatement :+: SimpleStatement) a])))
type Rep1 Module Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Module = D1 (MetaData "Module" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" False) (C1 (MetaCons "Module" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 (CompoundStatement :+: SimpleStatement))))

newtype AnonymousAwait a Source #

Constructors

AnonymousAwait 

Fields

Instances
Functor AnonymousAwait Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> AnonymousAwait a -> AnonymousAwait b #

(<$) :: a -> AnonymousAwait b -> AnonymousAwait a #

Foldable AnonymousAwait Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => AnonymousAwait m -> m #

foldMap :: Monoid m => (a -> m) -> AnonymousAwait a -> m #

foldr :: (a -> b -> b) -> b -> AnonymousAwait a -> b #

foldr' :: (a -> b -> b) -> b -> AnonymousAwait a -> b #

foldl :: (b -> a -> b) -> b -> AnonymousAwait a -> b #

foldl' :: (b -> a -> b) -> b -> AnonymousAwait a -> b #

foldr1 :: (a -> a -> a) -> AnonymousAwait a -> a #

foldl1 :: (a -> a -> a) -> AnonymousAwait a -> a #

toList :: AnonymousAwait a -> [a] #

null :: AnonymousAwait a -> Bool #

length :: AnonymousAwait a -> Int #

elem :: Eq a => a -> AnonymousAwait a -> Bool #

maximum :: Ord a => AnonymousAwait a -> a #

minimum :: Ord a => AnonymousAwait a -> a #

sum :: Num a => AnonymousAwait a -> a #

product :: Num a => AnonymousAwait a -> a #

Traversable AnonymousAwait Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> AnonymousAwait a -> f (AnonymousAwait b) #

sequenceA :: Applicative f => AnonymousAwait (f a) -> f (AnonymousAwait a) #

mapM :: Monad m => (a -> m b) -> AnonymousAwait a -> m (AnonymousAwait b) #

sequence :: Monad m => AnonymousAwait (m a) -> m (AnonymousAwait a) #

SymbolMatching AnonymousAwait Source # 
Instance details

Defined in TreeSitter.Python.AST

Unmarshal AnonymousAwait Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (AnonymousAwait a)

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 #

Generic1 AnonymousAwait Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 AnonymousAwait :: k -> Type #

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.5.0.0-inplace" True) (C1 (MetaCons "AnonymousAwait" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 AnonymousAwait Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 AnonymousAwait = D1 (MetaData "AnonymousAwait" "TreeSitter.Python.AST" "tree-sitter-python-0.5.0.0-inplace" True) (C1 (MetaCons "AnonymousAwait" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

data Comment a Source #

Constructors

Comment 

Fields

Instances
Functor Comment Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fmap :: (a -> b) -> Comment a -> Comment b #

(<$) :: a -> Comment b -> Comment a #

Foldable Comment Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

fold :: Monoid m => Comment m -> m #

foldMap :: Monoid m => (a -> m) -> Comment a -> m #

foldr :: (a -> b -> b) -> b -> Comment a -> b #

foldr' :: (a -> b -> b) -> b -> Comment a -> b #

foldl :: (b -> a -> b) -> b -> Comment a -> b #

foldl' :: (b -> a -> b) -> b -> Comment a -> b #

foldr1 :: (a -> a -> a) -> Comment a -> a #

foldl1 :: (a -> a -> a) -> Comment a -> a #

toList :: Comment a -> [a] #

null :: Comment a -> Bool #

length :: Comment a -> Int #

elem :: Eq a => a -> Comment a -> Bool #

maximum :: Ord a => Comment a -> a #

minimum :: Ord a => Comment a -> a #

sum :: Num a => Comment a -> a #

product :: Num a => Comment a -> a #

Traversable Comment Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

traverse :: Applicative f => (a -> f b) -> Comment a -> f (Comment b) #

sequenceA :: Applicative f => Comment (f a) -> f (Comment a) #

mapM :: Monad m => (a -> m b) -> Comment a -> m (Comment b) #

sequence :: Monad m => Comment (m a) -> m (Comment a) #

SymbolMatching Comment Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

symbolMatch :: Proxy Comment -> Node -> Bool

showFailure :: Proxy Comment -> Node -> String

Unmarshal Comment Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Comment a)

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 #

Generic1 Comment Source # 
Instance details

Defined in TreeSitter.Python.AST

Associated Types

type Rep1 Comment :: k -> Type #

Methods

from1 :: Comment a -> Rep1 Comment a #

to1 :: Rep1 Comment a -> Comment a #

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.5.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)))
type Rep1 Comment Source # 
Instance details

Defined in TreeSitter.Python.AST

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