tree-sitter-python-0.8.1.0: Tree-sitter grammar/parser for Python
Safe HaskellNone
LanguageHaskell2010

TreeSitter.Python.AST

Documentation

type AnonymousTilde = Token "~" 54 Source #

type AnonymousRBrace = Token "}" 82 Source #

type AnonymousPipeEqual = Token "|=" 76 Source #

type AnonymousPipe = Token "|" 50 Source #

type AnonymousLBrace = Token "{" 81 Source #

type AnonymousYield = Token "yield" 77 Source #

type AnonymousWith = Token "with" 32 Source #

type AnonymousWhile = Token "while" 28 Source #

data TypeConversion a Source #

Constructors

TypeConversion 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match TypeConversion)

matchers :: B (Int, Match TypeConversion)

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 #

Methods

from1 :: forall (a :: k). TypeConversion a -> Rep1 TypeConversion a #

to1 :: forall (a :: k). Rep1 TypeConversion a -> TypeConversion a #

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.8.1.0-inplace" 'False) (C1 ('MetaCons "TypeConversion" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") '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.8.1.0-inplace" 'False) (C1 ('MetaCons "TypeConversion" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

type AnonymousTry = Token "try" 29 Source #

data True a Source #

Constructors

True 

Fields

Instances

Instances details
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 #

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

matchedSymbols :: Proxy True -> [Int]

showFailure :: Proxy True -> Node -> String

Unmarshal True Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match True)

matchers :: B (Int, Match True)

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 :: forall (a :: k). True a -> Rep1 True a #

to1 :: forall (a :: k). 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.8.1.0-inplace" 'False) (C1 ('MetaCons "True" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type Rep1 True Source # 
Instance details

Defined in TreeSitter.Python.AST

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

type AnonymousReturn = Token "return" 15 Source #

type AnonymousRaise = Token "raise" 17 Source #

type AnonymousPrint = Token "print" 11 Source #

type AnonymousPass = Token "pass" 18 Source #

type AnonymousOr = Token "or" 44 Source #

type AnonymousNot = Token "not" 42 Source #

type AnonymousNonlocal = Token "nonlocal" 38 Source #

data None a Source #

Constructors

None 

Fields

Instances

Instances details
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 #

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

matchedSymbols :: Proxy None -> [Int]

showFailure :: Proxy None -> Node -> String

Unmarshal None Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match None)

matchers :: B (Int, Match None)

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 :: forall (a :: k). None a -> Rep1 None a #

to1 :: forall (a :: k). 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.8.1.0-inplace" 'False) (C1 ('MetaCons "None" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type Rep1 None Source # 
Instance details

Defined in TreeSitter.Python.AST

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

type AnonymousLambda = Token "lambda" 63 Source #

type AnonymousIs = Token "is" 62 Source #

data Integer a Source #

Constructors

Integer 

Fields

Instances

Instances details
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 #

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

Unmarshal Integer Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Integer)

matchers :: B (Int, Match Integer)

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 :: forall (a :: k). Integer a -> Rep1 Integer a #

to1 :: forall (a :: k). 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.8.1.0-inplace" 'False) (C1 ('MetaCons "Integer" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") '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.8.1.0-inplace" 'False) (C1 ('MetaCons "Integer" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

type AnonymousIn = Token "in" 27 Source #

type AnonymousImport = Token "import" 2 Source #

type AnonymousIf = Token "if" 21 Source #

data Identifier a Source #

Constructors

Identifier 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match Identifier)

matchers :: B (Int, Match Identifier)

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 #

Methods

from1 :: forall (a :: k). Identifier a -> Rep1 Identifier a #

to1 :: forall (a :: k). Rep1 Identifier a -> Identifier a #

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.8.1.0-inplace" 'False) (C1 ('MetaCons "Identifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") '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.8.1.0-inplace" 'False) (C1 ('MetaCons "Identifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

type AnonymousGlobal = Token "global" 37 Source #

type AnonymousFrom = Token "from" 4 Source #

type AnonymousFor = Token "for" 26 Source #

data Float a Source #

Constructors

Float 

Fields

Instances

Instances details
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 #

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

Unmarshal Float Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Float)

matchers :: B (Int, Match Float)

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 :: forall (a :: k). Float a -> Rep1 Float a #

to1 :: forall (a :: k). 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.8.1.0-inplace" 'False) (C1 ('MetaCons "Float" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") '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.8.1.0-inplace" 'False) (C1 ('MetaCons "Float" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

type AnonymousFinally = Token "finally" 31 Source #

data False a Source #

Constructors

False 

Fields

Instances

Instances details
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 #

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

Unmarshal False Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match False)

matchers :: B (Int, Match False)

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 :: forall (a :: k). False a -> Rep1 False a #

to1 :: forall (a :: k). 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.8.1.0-inplace" 'False) (C1 ('MetaCons "False" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") '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.8.1.0-inplace" 'False) (C1 ('MetaCons "False" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

type AnonymousExec = Token "exec" 39 Source #

type AnonymousExcept = Token "except" 30 Source #

data EscapeSequence a Source #

Constructors

EscapeSequence 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match EscapeSequence)

matchers :: B (Int, Match EscapeSequence)

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 #

Methods

from1 :: forall (a :: k). EscapeSequence a -> Rep1 EscapeSequence a #

to1 :: forall (a :: k). Rep1 EscapeSequence a -> EscapeSequence a #

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.8.1.0-inplace" 'False) (C1 ('MetaCons "EscapeSequence" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") '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.8.1.0-inplace" 'False) (C1 ('MetaCons "EscapeSequence" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

type AnonymousElse = Token "else" 24 Source #

data Ellipsis a Source #

Constructors

Ellipsis 

Fields

Instances

Instances details
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 #

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

Unmarshal Ellipsis Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Ellipsis)

matchers :: B (Int, Match Ellipsis)

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 :: forall (a :: k). Ellipsis a -> Rep1 Ellipsis a #

to1 :: forall (a :: k). 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.8.1.0-inplace" 'False) (C1 ('MetaCons "Ellipsis" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") '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.8.1.0-inplace" 'False) (C1 ('MetaCons "Ellipsis" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

type AnonymousElif = Token "elif" 23 Source #

type AnonymousDel = Token "del" 16 Source #

type AnonymousDef = Token "def" 33 Source #

type AnonymousContinue = Token "continue" 20 Source #

type AnonymousClass = Token "class" 40 Source #

type AnonymousBreak = Token "break" 19 Source #

type AnonymousAwait = Token "await" 92 Source #

type AnonymousAsync = Token "async" 25 Source #

type AnonymousAssert = Token "assert" 13 Source #

type AnonymousAs = Token "as" 9 Source #

type AnonymousAnd = Token "and" 43 Source #

type AnonymousUnderscorefutureUnderscore = Token "__future__" 5 Source #

type AnonymousCaretEqual = Token "^=" 75 Source #

type AnonymousCaret = Token "^" 52 Source #

type AnonymousRBracket = Token "]" 79 Source #

type AnonymousLBracket = Token "[" 78 Source #

type AnonymousAtEqual = Token "@=" 68 Source #

type AnonymousAt = Token "@" 41 Source #

type AnonymousRAngleRAngleEqual = Token ">>=" 72 Source #

type AnonymousRAngleRAngle = Token ">>" 12 Source #

type AnonymousRAngleEqual = Token ">=" 59 Source #

type AnonymousRAngle = Token ">" 60 Source #

type AnonymousEqualEqual = Token "==" 57 Source #

type AnonymousEqual = Token "=" 35 Source #

type AnonymousLAngleRAngle = Token "<>" 61 Source #

type AnonymousLAngleEqual = Token "<=" 56 Source #

type AnonymousLAngleLAngleEqual = Token "<<=" 73 Source #

type AnonymousLAngleLAngle = Token "<<" 53 Source #

type AnonymousLAngle = Token "<" 55 Source #

type AnonymousColonEqual = Token ":=" 14 Source #

type AnonymousColon = Token ":" 22 Source #

type AnonymousSlashEqual = Token "/=" 67 Source #

type AnonymousSlashSlashEqual = Token "//=" 69 Source #

type AnonymousSlashSlash = Token "//" 49 Source #

type AnonymousSlash = Token "/" 47 Source #

type AnonymousDot = Token "." 3 Source #

type AnonymousMinusRAngle = Token "->" 34 Source #

type AnonymousMinusEqual = Token "-=" 65 Source #

type AnonymousMinus = Token "-" 46 Source #

type AnonymousComma = Token "," 8 Source #

type AnonymousPlusEqual = Token "+=" 64 Source #

type AnonymousPlus = Token "+" 45 Source #

type AnonymousStarEqual = Token "*=" 66 Source #

type AnonymousStarStarEqual = Token "**=" 71 Source #

type AnonymousStarStar = Token "**" 36 Source #

type AnonymousStar = Token "*" 10 Source #

type AnonymousRParen = Token ")" 7 Source #

type AnonymousLParen = Token "(" 6 Source #

type AnonymousAmpersandEqual = Token "&=" 74 Source #

type AnonymousAmpersand = Token "&" 51 Source #

type AnonymousPercentEqual = Token "%=" 70 Source #

type AnonymousPercent = Token "%" 48 Source #

type AnonymousBangEqual = Token "!=" 58 Source #

data Yield a Source #

Constructors

Yield 

Instances

Instances details
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 #

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

Unmarshal Yield Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Yield)

matchers :: B (Int, Match Yield)

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 :: forall (a :: k). Yield a -> Rep1 Yield a #

to1 :: forall (a :: k). 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.8.1.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.8.1.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 WithStatement a Source #

Constructors

WithStatement 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match WithStatement)

matchers :: B (Int, Match WithStatement)

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 #

Methods

from1 :: forall (a :: k). WithStatement a -> Rep1 WithStatement a #

to1 :: forall (a :: k). Rep1 WithStatement a -> WithStatement a #

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.8.1.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.8.1.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 WithItem a Source #

Constructors

WithItem 

Fields

Instances

Instances details
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 #

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

Unmarshal WithItem Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match WithItem)

matchers :: B (Int, Match WithItem)

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 :: forall (a :: k). WithItem a -> Rep1 WithItem a #

to1 :: forall (a :: k). 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.8.1.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

type Rep1 WithItem = D1 ('MetaData "WithItem" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "WithItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Expression) :*: S1 ('MetaSel ('Just "alias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 Expression))))

data WildcardImport a Source #

Constructors

WildcardImport 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match WildcardImport)

matchers :: B (Int, Match WildcardImport)

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 #

Methods

from1 :: forall (a :: k). WildcardImport a -> Rep1 WildcardImport a #

to1 :: forall (a :: k). Rep1 WildcardImport a -> WildcardImport a #

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.8.1.0-inplace" 'False) (C1 ('MetaCons "WildcardImport" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") '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.8.1.0-inplace" 'False) (C1 ('MetaCons "WildcardImport" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data WhileStatement a Source #

Constructors

WhileStatement 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match WhileStatement)

matchers :: B (Int, Match WhileStatement)

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 #

Methods

from1 :: forall (a :: k). WhileStatement a -> Rep1 WhileStatement a #

to1 :: forall (a :: k). Rep1 WhileStatement a -> WhileStatement a #

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.8.1.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

type Rep1 WhileStatement = D1 ('MetaData "WhileStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "WhileStatement" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "alternative") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ElseClause)) :*: (S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Block) :*: S1 ('MetaSel ('Just "condition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Expression))))

data Variables a Source #

Constructors

Variables 

Instances

Instances details
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 #

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

Unmarshal Variables Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Variables)

matchers :: B (Int, Match Variables)

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 #

Methods

from1 :: forall (a :: k). Variables a -> Rep1 Variables a #

to1 :: forall (a :: k). Rep1 Variables a -> Variables a #

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.8.1.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.8.1.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 UnaryOperator a Source #

Instances

Instances details
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 #

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

matchers' :: IntMap (Match UnaryOperator)

matchers :: B (Int, Match UnaryOperator)

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 #

Methods

from1 :: forall (a :: k). UnaryOperator a -> Rep1 UnaryOperator a #

to1 :: forall (a :: k). Rep1 UnaryOperator a -> UnaryOperator a #

type Rep (UnaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (UnaryOperator a) = D1 ('MetaData "UnaryOperator" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "UnaryOperator" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "operator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((AnonymousPlus :+: (AnonymousMinus :+: AnonymousTilde)) a)) :*: S1 ('MetaSel ('Just "argument") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PrimaryExpression a)))))
type Rep1 UnaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 UnaryOperator = D1 ('MetaData "UnaryOperator" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "UnaryOperator" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "operator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (AnonymousPlus :+: (AnonymousMinus :+: AnonymousTilde))) :*: S1 ('MetaSel ('Just "argument") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 PrimaryExpression))))

data TypedParameter a Source #

Instances

Instances details
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 #

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

matchers' :: IntMap (Match TypedParameter)

matchers :: B (Int, Match TypedParameter)

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 #

Methods

from1 :: forall (a :: k). TypedParameter a -> Rep1 TypedParameter a #

to1 :: forall (a :: k). Rep1 TypedParameter a -> TypedParameter a #

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.8.1.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

type Rep1 TypedParameter = D1 ('MetaData "TypedParameter" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "TypedParameter" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "type'") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Type) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (DictionarySplat :+: (Identifier :+: ListSplat))))))

data TypedDefaultParameter a Source #

Constructors

TypedDefaultParameter 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). TypedDefaultParameter a -> Rep1 TypedDefaultParameter a #

to1 :: forall (a :: k). Rep1 TypedDefaultParameter a -> TypedDefaultParameter a #

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.8.1.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

type Rep1 TypedDefaultParameter = D1 ('MetaData "TypedDefaultParameter" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "TypedDefaultParameter" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Expression)) :*: (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Identifier) :*: S1 ('MetaSel ('Just "type'") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Type))))

data Type a Source #

Constructors

Type 

Fields

Instances

Instances details
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 #

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

matchedSymbols :: Proxy Type -> [Int]

showFailure :: Proxy Type -> Node -> String

Unmarshal Type Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Type)

matchers :: B (Int, Match Type)

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 :: forall (a :: k). Type a -> Rep1 Type a #

to1 :: forall (a :: k). 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.8.1.0-inplace" 'False) (C1 ('MetaCons "Type" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))))
type Rep1 Type Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Type = D1 ('MetaData "Type" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "Type" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Expression)))

data Tuple a Source #

Constructors

Tuple 

Fields

Instances

Instances details
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 #

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

Unmarshal Tuple Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Tuple)

matchers :: B (Int, Match Tuple)

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 :: forall (a :: k). Tuple a -> Rep1 Tuple a #

to1 :: forall (a :: k). 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.8.1.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.8.1.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 TryStatement a Source #

Instances

Instances details
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 #

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

matchers' :: IntMap (Match TryStatement)

matchers :: B (Int, Match TryStatement)

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 #

Methods

from1 :: forall (a :: k). TryStatement a -> Rep1 TryStatement a #

to1 :: forall (a :: k). Rep1 TryStatement a -> TryStatement a #

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.8.1.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

type Rep1 TryStatement = D1 ('MetaData "TryStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "TryStatement" '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 (ElseClause :+: (ExceptClause :+: FinallyClause))))))

data Subscript a Source #

Instances

Instances details
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 #

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

Unmarshal Subscript Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Subscript)

matchers :: B (Int, Match Subscript)

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 #

Methods

from1 :: forall (a :: k). Subscript a -> Rep1 Subscript a #

to1 :: forall (a :: k). Rep1 Subscript a -> Subscript a #

type Rep (Subscript a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Subscript a) = D1 ('MetaData "Subscript" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "Subscript" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "subscript") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty ((AnonymousComma :+: (Expression :+: Slice)) a))) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PrimaryExpression a)))))
type Rep1 Subscript Source # 
Instance details

Defined in TreeSitter.Python.AST

data String a Source #

Constructors

String 

Instances

Instances details
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 #

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

Unmarshal String Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match String)

matchers :: B (Int, Match String)

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 :: forall (a :: k). String a -> Rep1 String a #

to1 :: forall (a :: k). 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.8.1.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.8.1.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 Slice a Source #

Constructors

Slice 

Fields

Instances

Instances details
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 #

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

Unmarshal Slice Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Slice)

matchers :: B (Int, Match Slice)

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 :: forall (a :: k). Slice a -> Rep1 Slice a #

to1 :: forall (a :: k). 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.8.1.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.8.1.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 SetComprehension a Source #

Constructors

SetComprehension 

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). SetComprehension a -> Rep1 SetComprehension a #

to1 :: forall (a :: k). Rep1 SetComprehension a -> SetComprehension a #

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.8.1.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

type Rep1 SetComprehension = D1 ('MetaData "SetComprehension" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "SetComprehension" '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 Set a Source #

Constructors

Set 

Instances

Instances details
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 #

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

matchedSymbols :: Proxy Set -> [Int]

showFailure :: Proxy Set -> Node -> String

Unmarshal Set Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Set)

matchers :: B (Int, Match Set)

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 :: forall (a :: k). Set a -> Rep1 Set a #

to1 :: forall (a :: k). 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.8.1.0-inplace" 'False) (C1 ('MetaCons "Set" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty ((Expression :+: ListSplat) a)))))
type Rep1 Set Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Set = D1 ('MetaData "Set" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "Set" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (NonEmpty :.: Rec1 (Expression :+: ListSplat))))

data ReturnStatement a Source #

Constructors

ReturnStatement 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). ReturnStatement a -> Rep1 ReturnStatement a #

to1 :: forall (a :: k). Rep1 ReturnStatement a -> ReturnStatement a #

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.8.1.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.8.1.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 RelativeImport a Source #

Instances

Instances details
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 #

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

matchers' :: IntMap (Match RelativeImport)

matchers :: B (Int, Match RelativeImport)

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 #

Methods

from1 :: forall (a :: k). RelativeImport a -> Rep1 RelativeImport a #

to1 :: forall (a :: k). Rep1 RelativeImport a -> RelativeImport a #

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.8.1.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.8.1.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 RaiseStatement a Source #

Constructors

RaiseStatement 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match RaiseStatement)

matchers :: B (Int, Match RaiseStatement)

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 #

Methods

from1 :: forall (a :: k). RaiseStatement a -> Rep1 RaiseStatement a #

to1 :: forall (a :: k). Rep1 RaiseStatement a -> RaiseStatement a #

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.8.1.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

type Rep1 RaiseStatement = D1 ('MetaData "RaiseStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "RaiseStatement" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "cause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 Expression) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ExpressionList))))

data PrintStatement a Source #

Constructors

PrintStatement 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match PrintStatement)

matchers :: B (Int, Match PrintStatement)

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 #

Methods

from1 :: forall (a :: k). PrintStatement a -> Rep1 PrintStatement a #

to1 :: forall (a :: k). Rep1 PrintStatement a -> PrintStatement a #

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.8.1.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 (Maybe (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.8.1.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) (Maybe :.: Rec1 Chevron))))

data PassStatement a Source #

Constructors

PassStatement 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match PassStatement)

matchers :: B (Int, Match PassStatement)

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 #

Methods

from1 :: forall (a :: k). PassStatement a -> Rep1 PassStatement a #

to1 :: forall (a :: k). Rep1 PassStatement a -> PassStatement a #

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.8.1.0-inplace" 'False) (C1 ('MetaCons "PassStatement" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") '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.8.1.0-inplace" 'False) (C1 ('MetaCons "PassStatement" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data ParenthesizedExpression a Source #

Instances

Instances details
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 #

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

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.8.1.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 :+: ListSplat) :+: (ParenthesizedExpression :+: 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.8.1.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 :+: ListSplat) :+: (ParenthesizedExpression :+: Yield)))))

data Parameters a Source #

Constructors

Parameters 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match Parameters)

matchers :: B (Int, Match Parameters)

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 #

Methods

from1 :: forall (a :: k). Parameters a -> Rep1 Parameters a #

to1 :: forall (a :: k). Rep1 Parameters a -> Parameters a #

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.8.1.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.8.1.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 Pair a Source #

Constructors

Pair 

Fields

Instances

Instances details
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 #

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

matchedSymbols :: Proxy Pair -> [Int]

showFailure :: Proxy Pair -> Node -> String

Unmarshal Pair Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Pair)

matchers :: B (Int, Match Pair)

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 :: forall (a :: k). Pair a -> Rep1 Pair a #

to1 :: forall (a :: k). Rep1 Pair a -> Pair a #

type Rep (Pair a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Pair a) = D1 ('MetaData "Pair" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "Pair" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Just "key") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))))
type Rep1 Pair Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Pair = D1 ('MetaData "Pair" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "Pair" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Expression) :*: S1 ('MetaSel ('Just "key") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Expression))))

data NotOperator a Source #

Constructors

NotOperator 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match NotOperator)

matchers :: B (Int, Match NotOperator)

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 #

Methods

from1 :: forall (a :: k). NotOperator a -> Rep1 NotOperator a #

to1 :: forall (a :: k). Rep1 NotOperator a -> NotOperator a #

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.8.1.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.8.1.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 NonlocalStatement a Source #

Constructors

NonlocalStatement 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). NonlocalStatement a -> Rep1 NonlocalStatement a #

to1 :: forall (a :: k). Rep1 NonlocalStatement a -> NonlocalStatement a #

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.8.1.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.8.1.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 NamedExpression a Source #

Constructors

NamedExpression 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). NamedExpression a -> Rep1 NamedExpression a #

to1 :: forall (a :: k). Rep1 NamedExpression a -> NamedExpression a #

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.8.1.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

type Rep1 NamedExpression = D1 ('MetaData "NamedExpression" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "NamedExpression" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Expression) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Identifier))))

data Module a Source #

Constructors

Module 

Instances

Instances details
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 #

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

Unmarshal Module Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Module)

matchers :: B (Int, Match Module)

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 :: forall (a :: k). Module a -> Rep1 Module a #

to1 :: forall (a :: k). 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.8.1.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.8.1.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))))

data ListSplat a Source #

Constructors

ListSplat 

Fields

Instances

Instances details
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 #

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

Unmarshal ListSplat Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match ListSplat)

matchers :: B (Int, Match ListSplat)

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 #

Methods

from1 :: forall (a :: k). ListSplat a -> Rep1 ListSplat a #

to1 :: forall (a :: k). Rep1 ListSplat a -> ListSplat a #

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.8.1.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.8.1.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 ListComprehension a Source #

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). ListComprehension a -> Rep1 ListComprehension a #

to1 :: forall (a :: k). Rep1 ListComprehension a -> ListComprehension a #

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.8.1.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

type Rep1 ListComprehension = D1 ('MetaData "ListComprehension" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "ListComprehension" '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 List a Source #

Constructors

List 

Fields

Instances

Instances details
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 #

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

matchedSymbols :: Proxy List -> [Int]

showFailure :: Proxy List -> Node -> String

Unmarshal List Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match List)

matchers :: B (Int, Match List)

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 :: forall (a :: k). List a -> Rep1 List a #

to1 :: forall (a :: k). 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.8.1.0-inplace" 'False) (C1 ('MetaCons "List" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Expression :+: ListSplat) a])))
type Rep1 List Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 List = D1 ('MetaData "List" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "List" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 (Expression :+: ListSplat))))

data LambdaParameters a Source #

Constructors

LambdaParameters 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). LambdaParameters a -> Rep1 LambdaParameters a #

to1 :: forall (a :: k). Rep1 LambdaParameters a -> LambdaParameters a #

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.8.1.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.8.1.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 Lambda a Source #

Constructors

Lambda 

Instances

Instances details
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 #

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

Unmarshal Lambda Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Lambda)

matchers :: B (Int, Match Lambda)

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 :: forall (a :: k). Lambda a -> Rep1 Lambda a #

to1 :: forall (a :: k). 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.8.1.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

type Rep1 Lambda = D1 ('MetaData "Lambda" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "Lambda" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (Expression :+: Lambda)) :*: S1 ('MetaSel ('Just "parameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 LambdaParameters))))

data KeywordArgument a Source #

Constructors

KeywordArgument 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). KeywordArgument a -> Rep1 KeywordArgument a #

to1 :: forall (a :: k). Rep1 KeywordArgument a -> KeywordArgument a #

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.8.1.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

type Rep1 KeywordArgument = D1 ('MetaData "KeywordArgument" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "KeywordArgument" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Expression) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Identifier))))

data Interpolation a Source #

Instances

Instances details
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 #

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

matchers' :: IntMap (Match Interpolation)

matchers :: B (Int, Match Interpolation)

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 #

Methods

from1 :: forall (a :: k). Interpolation a -> Rep1 Interpolation a #

to1 :: forall (a :: k). Rep1 Interpolation a -> Interpolation a #

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.8.1.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.8.1.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 ImportStatement a Source #

Constructors

ImportStatement 

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). ImportStatement a -> Rep1 ImportStatement a #

to1 :: forall (a :: k). Rep1 ImportStatement a -> ImportStatement a #

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.8.1.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 (NonEmpty ((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.8.1.0-inplace" 'False) (C1 ('MetaCons "ImportStatement" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (NonEmpty :.: Rec1 (AliasedImport :+: DottedName))))

data ImportPrefix a Source #

Constructors

ImportPrefix 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match ImportPrefix)

matchers :: B (Int, Match ImportPrefix)

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 #

Methods

from1 :: forall (a :: k). ImportPrefix a -> Rep1 ImportPrefix a #

to1 :: forall (a :: k). Rep1 ImportPrefix a -> ImportPrefix a #

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.8.1.0-inplace" 'False) (C1 ('MetaCons "ImportPrefix" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") '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.8.1.0-inplace" 'False) (C1 ('MetaCons "ImportPrefix" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data ImportFromStatement a Source #

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). ImportFromStatement a -> Rep1 ImportFromStatement a #

to1 :: forall (a :: k). Rep1 ImportFromStatement a -> ImportFromStatement a #

type Rep (ImportFromStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ImportFromStatement a) = D1 ('MetaData "ImportFromStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "ImportFromStatement" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(AliasedImport :+: DottedName) a])) :*: (S1 ('MetaSel ('Just "moduleName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((DottedName :+: RelativeImport) a)) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (WildcardImport a))))))
type Rep1 ImportFromStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

data IfStatement a Source #

Constructors

IfStatement 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match IfStatement)

matchers :: B (Int, Match IfStatement)

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 #

Methods

from1 :: forall (a :: k). IfStatement a -> Rep1 IfStatement a #

to1 :: forall (a :: k). Rep1 IfStatement a -> IfStatement a #

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.8.1.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

type Rep1 IfStatement = D1 ('MetaData "IfStatement" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "IfStatement" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "alternative") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 (ElifClause :+: ElseClause))) :*: (S1 ('MetaSel ('Just "consequence") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Block) :*: S1 ('MetaSel ('Just "condition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Expression))))

data IfClause a Source #

Constructors

IfClause 

Fields

Instances

Instances details
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 #

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

Unmarshal IfClause Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match IfClause)

matchers :: B (Int, Match IfClause)

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 :: forall (a :: k). IfClause a -> Rep1 IfClause a #

to1 :: forall (a :: k). 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.8.1.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.8.1.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 GlobalStatement a Source #

Constructors

GlobalStatement 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). GlobalStatement a -> Rep1 GlobalStatement a #

to1 :: forall (a :: k). Rep1 GlobalStatement a -> GlobalStatement a #

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.8.1.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.8.1.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 GeneratorExpression a Source #

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). GeneratorExpression a -> Rep1 GeneratorExpression a #

to1 :: forall (a :: k). Rep1 GeneratorExpression a -> GeneratorExpression a #

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.8.1.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.8.1.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 FutureImportStatement a Source #

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). FutureImportStatement a -> Rep1 FutureImportStatement a #

to1 :: forall (a :: k). Rep1 FutureImportStatement a -> FutureImportStatement a #

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.8.1.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 (NonEmpty ((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.8.1.0-inplace" 'False) (C1 ('MetaCons "FutureImportStatement" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (NonEmpty :.: Rec1 (AliasedImport :+: DottedName))))

data FunctionDefinition a Source #

Constructors

FunctionDefinition 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). FunctionDefinition a -> Rep1 FunctionDefinition a #

to1 :: forall (a :: k). Rep1 FunctionDefinition a -> FunctionDefinition a #

type Rep (FunctionDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (FunctionDefinition a) = D1 ('MetaData "FunctionDefinition" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "FunctionDefinition" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "returnType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Type a)))) :*: (S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Block a)) :*: (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Identifier a)) :*: S1 ('MetaSel ('Just "parameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Parameters a))))))
type Rep1 FunctionDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

data FormatSpecifier a Source #

Constructors

FormatSpecifier 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). FormatSpecifier a -> Rep1 FormatSpecifier a #

to1 :: forall (a :: k). Rep1 FormatSpecifier a -> FormatSpecifier a #

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.8.1.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.8.1.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

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). FormatExpression a -> Rep1 FormatExpression a #

to1 :: forall (a :: k). Rep1 FormatExpression a -> FormatExpression a #

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.8.1.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.8.1.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 ForStatement a Source #

Constructors

ForStatement 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match ForStatement)

matchers :: B (Int, Match ForStatement)

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 #

Methods

from1 :: forall (a :: k). ForStatement a -> Rep1 ForStatement a #

to1 :: forall (a :: k). Rep1 ForStatement a -> ForStatement a #

type Rep (ForStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ForStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

data ForInClause a Source #

Constructors

ForInClause 

Instances

Instances details
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 #

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

matchers' :: IntMap (Match ForInClause)

matchers :: B (Int, Match ForInClause)

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 #

Methods

from1 :: forall (a :: k). ForInClause a -> Rep1 ForInClause a #

to1 :: forall (a :: k). Rep1 ForInClause a -> ForInClause a #

type Rep (ForInClause a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ForInClause a) = D1 ('MetaData "ForInClause" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "ForInClause" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "left") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Variables a)) :*: S1 ('MetaSel ('Just "right") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty ((AnonymousComma :+: (Expression :+: Lambda)) a))))))
type Rep1 ForInClause Source # 
Instance details

Defined in TreeSitter.Python.AST

data FinallyClause a Source #

Constructors

FinallyClause 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match FinallyClause)

matchers :: B (Int, Match FinallyClause)

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 #

Methods

from1 :: forall (a :: k). FinallyClause a -> Rep1 FinallyClause a #

to1 :: forall (a :: k). Rep1 FinallyClause a -> FinallyClause a #

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.8.1.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.8.1.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 ExpressionStatement a Source #

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). ExpressionStatement a -> Rep1 ExpressionStatement a #

to1 :: forall (a :: k). Rep1 ExpressionStatement a -> ExpressionStatement a #

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.8.1.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.8.1.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 ExpressionList a Source #

Constructors

ExpressionList 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match ExpressionList)

matchers :: B (Int, Match ExpressionList)

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 #

Methods

from1 :: forall (a :: k). ExpressionList a -> Rep1 ExpressionList a #

to1 :: forall (a :: k). Rep1 ExpressionList a -> ExpressionList a #

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.8.1.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.8.1.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 ExecStatement a Source #

Constructors

ExecStatement 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match ExecStatement)

matchers :: B (Int, Match ExecStatement)

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 #

Methods

from1 :: forall (a :: k). ExecStatement a -> Rep1 ExecStatement a #

to1 :: forall (a :: k). Rep1 ExecStatement a -> ExecStatement a #

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.8.1.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.8.1.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 ExceptClause a Source #

Constructors

ExceptClause 

Instances

Instances details
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 #

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

matchers' :: IntMap (Match ExceptClause)

matchers :: B (Int, Match ExceptClause)

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 #

Methods

from1 :: forall (a :: k). ExceptClause a -> Rep1 ExceptClause a #

to1 :: forall (a :: k). Rep1 ExceptClause a -> ExceptClause a #

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.8.1.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.8.1.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 ElseClause a Source #

Constructors

ElseClause 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match ElseClause)

matchers :: B (Int, Match ElseClause)

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 #

Methods

from1 :: forall (a :: k). ElseClause a -> Rep1 ElseClause a #

to1 :: forall (a :: k). Rep1 ElseClause a -> ElseClause a #

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.8.1.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.8.1.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 ElifClause a Source #

Constructors

ElifClause 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match ElifClause)

matchers :: B (Int, Match ElifClause)

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 #

Methods

from1 :: forall (a :: k). ElifClause a -> Rep1 ElifClause a #

to1 :: forall (a :: k). Rep1 ElifClause a -> ElifClause a #

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.8.1.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.8.1.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 DottedName a Source #

Constructors

DottedName 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match DottedName)

matchers :: B (Int, Match DottedName)

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 #

Methods

from1 :: forall (a :: k). DottedName a -> Rep1 DottedName a #

to1 :: forall (a :: k). Rep1 DottedName a -> DottedName a #

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.8.1.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.8.1.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 DictionarySplat a Source #

Constructors

DictionarySplat 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). DictionarySplat a -> Rep1 DictionarySplat a #

to1 :: forall (a :: k). Rep1 DictionarySplat a -> DictionarySplat a #

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.8.1.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.8.1.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 DictionaryComprehension a Source #

Instances

Instances details
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 #

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

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.8.1.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.8.1.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 Dictionary a Source #

Constructors

Dictionary 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match Dictionary)

matchers :: B (Int, Match Dictionary)

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 #

Methods

from1 :: forall (a :: k). Dictionary a -> Rep1 Dictionary a #

to1 :: forall (a :: k). Rep1 Dictionary a -> Dictionary a #

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.8.1.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.8.1.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 DeleteStatement a Source #

Constructors

DeleteStatement 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). DeleteStatement a -> Rep1 DeleteStatement a #

to1 :: forall (a :: k). Rep1 DeleteStatement a -> DeleteStatement a #

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.8.1.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.8.1.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 DefaultParameter a Source #

Constructors

DefaultParameter 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). DefaultParameter a -> Rep1 DefaultParameter a #

to1 :: forall (a :: k). Rep1 DefaultParameter a -> DefaultParameter a #

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.8.1.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

type Rep1 DefaultParameter = D1 ('MetaData "DefaultParameter" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "DefaultParameter" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Expression) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Identifier))))

data Decorator a Source #

Constructors

Decorator 

Fields

Instances

Instances details
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 #

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

Unmarshal Decorator Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Decorator)

matchers :: B (Int, Match Decorator)

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 #

Methods

from1 :: forall (a :: k). Decorator a -> Rep1 Decorator a #

to1 :: forall (a :: k). Rep1 Decorator a -> Decorator a #

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.8.1.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

type Rep1 Decorator = D1 ('MetaData "Decorator" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "Decorator" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "arguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ArgumentList) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DottedName))))

data DecoratedDefinition a Source #

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). DecoratedDefinition a -> Rep1 DecoratedDefinition a #

to1 :: forall (a :: k). Rep1 DecoratedDefinition a -> DecoratedDefinition a #

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.8.1.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

type Rep1 DecoratedDefinition = D1 ('MetaData "DecoratedDefinition" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "DecoratedDefinition" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "definition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (ClassDefinition :+: FunctionDefinition)) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (NonEmpty :.: Rec1 Decorator))))

data ContinueStatement a Source #

Constructors

ContinueStatement 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). ContinueStatement a -> Rep1 ContinueStatement a #

to1 :: forall (a :: k). Rep1 ContinueStatement a -> ContinueStatement a #

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.8.1.0-inplace" 'False) (C1 ('MetaCons "ContinueStatement" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") '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.8.1.0-inplace" 'False) (C1 ('MetaCons "ContinueStatement" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data ConditionalExpression a Source #

Constructors

ConditionalExpression 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). ConditionalExpression a -> Rep1 ConditionalExpression a #

to1 :: forall (a :: k). Rep1 ConditionalExpression a -> ConditionalExpression a #

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.8.1.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.8.1.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 ConcatenatedString a Source #

Constructors

ConcatenatedString 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). ConcatenatedString a -> Rep1 ConcatenatedString a #

to1 :: forall (a :: k). Rep1 ConcatenatedString a -> ConcatenatedString a #

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.8.1.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.8.1.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 ComparisonOperator a Source #

Constructors

ComparisonOperator 

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). ComparisonOperator a -> Rep1 ComparisonOperator a #

to1 :: forall (a :: k). Rep1 ComparisonOperator a -> ComparisonOperator a #

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.8.1.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.8.1.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 ClassDefinition a Source #

Constructors

ClassDefinition 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). ClassDefinition a -> Rep1 ClassDefinition a #

to1 :: forall (a :: k). Rep1 ClassDefinition a -> ClassDefinition a #

type Rep (ClassDefinition a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (ClassDefinition a) = D1 ('MetaData "ClassDefinition" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "ClassDefinition" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Block a))) :*: (S1 ('MetaSel ('Just "superclasses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ArgumentList a))) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Identifier a)))))
type Rep1 ClassDefinition Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 ClassDefinition = D1 ('MetaData "ClassDefinition" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "ClassDefinition" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Block)) :*: (S1 ('MetaSel ('Just "superclasses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ArgumentList) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Identifier))))

data Chevron a Source #

Constructors

Chevron 

Fields

Instances

Instances details
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 #

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

Unmarshal Chevron Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Chevron)

matchers :: B (Int, Match Chevron)

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 :: forall (a :: k). Chevron a -> Rep1 Chevron a #

to1 :: forall (a :: k). 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.8.1.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.8.1.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 Call a Source #

Instances

Instances details
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 #

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

matchedSymbols :: Proxy Call -> [Int]

showFailure :: Proxy Call -> Node -> String

Unmarshal Call Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Call)

matchers :: B (Int, Match Call)

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 :: forall (a :: k). Call a -> Rep1 Call a #

to1 :: forall (a :: k). Rep1 Call a -> Call a #

type Rep (Call a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Call a) = D1 ('MetaData "Call" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "Call" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "function") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PrimaryExpression a)) :*: S1 ('MetaSel ('Just "arguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((ArgumentList :+: GeneratorExpression) a)))))
type Rep1 Call Source # 
Instance details

Defined in TreeSitter.Python.AST

data BreakStatement a Source #

Constructors

BreakStatement 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match BreakStatement)

matchers :: B (Int, Match BreakStatement)

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 #

Methods

from1 :: forall (a :: k). BreakStatement a -> Rep1 BreakStatement a #

to1 :: forall (a :: k). Rep1 BreakStatement a -> BreakStatement a #

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.8.1.0-inplace" 'False) (C1 ('MetaCons "BreakStatement" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") '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.8.1.0-inplace" 'False) (C1 ('MetaCons "BreakStatement" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data BooleanOperator a Source #

Constructors

BooleanOperator 

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). BooleanOperator a -> Rep1 BooleanOperator a #

to1 :: forall (a :: k). Rep1 BooleanOperator a -> BooleanOperator a #

type Rep (BooleanOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (BooleanOperator a) = D1 ('MetaData "BooleanOperator" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "BooleanOperator" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "operator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((AnonymousAnd :+: AnonymousOr) a))) :*: (S1 ('MetaSel ('Just "left") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Just "right") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))))
type Rep1 BooleanOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

data Block a Source #

Constructors

Block 

Instances

Instances details
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 #

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

Unmarshal Block Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Block)

matchers :: B (Int, Match Block)

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 :: forall (a :: k). Block a -> Rep1 Block a #

to1 :: forall (a :: k). 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.8.1.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.8.1.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 BinaryOperator a Source #

Instances

Instances details
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 #

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

matchers' :: IntMap (Match BinaryOperator)

matchers :: B (Int, Match BinaryOperator)

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 #

Methods

from1 :: forall (a :: k). BinaryOperator a -> Rep1 BinaryOperator a #

to1 :: forall (a :: k). Rep1 BinaryOperator a -> BinaryOperator a #

type Rep (BinaryOperator a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 BinaryOperator Source # 
Instance details

Defined in TreeSitter.Python.AST

data Await a Source #

Constructors

Await 

Fields

Instances

Instances details
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 #

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

Unmarshal Await Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Await)

matchers :: B (Int, Match Await)

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 :: forall (a :: k). Await a -> Rep1 Await a #

to1 :: forall (a :: k). 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.8.1.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.8.1.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 AugmentedAssignment a Source #

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). AugmentedAssignment a -> Rep1 AugmentedAssignment a #

to1 :: forall (a :: k). Rep1 AugmentedAssignment a -> AugmentedAssignment a #

type Rep (AugmentedAssignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 AugmentedAssignment Source # 
Instance details

Defined in TreeSitter.Python.AST

data Attribute a Source #

Constructors

Attribute 

Fields

Instances

Instances details
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 #

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

Unmarshal Attribute Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Attribute)

matchers :: B (Int, Match Attribute)

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 #

Methods

from1 :: forall (a :: k). Attribute a -> Rep1 Attribute a #

to1 :: forall (a :: k). Rep1 Attribute a -> Attribute a #

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.8.1.0-inplace" 'False) (C1 ('MetaCons "Attribute" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "attribute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Identifier a)) :*: S1 ('MetaSel ('Just "object") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PrimaryExpression 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.8.1.0-inplace" 'False) (C1 ('MetaCons "Attribute" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "attribute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Identifier) :*: S1 ('MetaSel ('Just "object") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 PrimaryExpression))))

data Assignment a Source #

Instances

Instances details
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 #

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

matchers' :: IntMap (Match Assignment)

matchers :: B (Int, Match Assignment)

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 #

Methods

from1 :: forall (a :: k). Assignment a -> Rep1 Assignment a #

to1 :: forall (a :: k). Rep1 Assignment a -> Assignment a #

type Rep (Assignment a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Assignment Source # 
Instance details

Defined in TreeSitter.Python.AST

data AssertStatement a Source #

Constructors

AssertStatement 

Fields

Instances

Instances details
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 #

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

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 #

Methods

from1 :: forall (a :: k). AssertStatement a -> Rep1 AssertStatement a #

to1 :: forall (a :: k). Rep1 AssertStatement a -> AssertStatement a #

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.8.1.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.8.1.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 ArgumentList a Source #

Instances

Instances details
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 #

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

matchers' :: IntMap (Match ArgumentList)

matchers :: B (Int, Match ArgumentList)

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 #

Methods

from1 :: forall (a :: k). ArgumentList a -> Rep1 ArgumentList a #

to1 :: forall (a :: k). Rep1 ArgumentList a -> ArgumentList a #

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.8.1.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 :+: ParenthesizedExpression))) 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.8.1.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 :+: ParenthesizedExpression))))))

data AliasedImport a Source #

Constructors

AliasedImport 

Fields

Instances

Instances details
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 #

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

matchers' :: IntMap (Match AliasedImport)

matchers :: B (Int, Match AliasedImport)

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 #

Methods

from1 :: forall (a :: k). AliasedImport a -> Rep1 AliasedImport a #

to1 :: forall (a :: k). Rep1 AliasedImport a -> AliasedImport a #

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.8.1.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

type Rep1 AliasedImport = D1 ('MetaData "AliasedImport" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'False) (C1 ('MetaCons "AliasedImport" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "alias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Identifier) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DottedName))))

newtype SimpleStatement a Source #

Instances

Instances details
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 #

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

HasField "ann" (SimpleStatement a) a Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

getField :: SimpleStatement a -> 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 #

Methods

from1 :: forall (a :: k). SimpleStatement a -> Rep1 SimpleStatement a #

to1 :: forall (a :: k). Rep1 SimpleStatement a -> SimpleStatement a #

type Rep (SimpleStatement a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 SimpleStatement Source # 
Instance details

Defined in TreeSitter.Python.AST

newtype PrimaryExpression a Source #

Instances

Instances details
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 #

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

HasField "ann" (PrimaryExpression a) a Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

getField :: PrimaryExpression a -> 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 #

Methods

from1 :: forall (a :: k). PrimaryExpression a -> Rep1 PrimaryExpression a #

to1 :: forall (a :: k). Rep1 PrimaryExpression a -> PrimaryExpression a #

type Rep (PrimaryExpression a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 PrimaryExpression Source # 
Instance details

Defined in TreeSitter.Python.AST

newtype Parameter a Source #

Instances

Instances details
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 #

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

Unmarshal Parameter Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

matchers' :: IntMap (Match Parameter)

matchers :: B (Int, Match Parameter)

HasField "ann" (Parameter a) a Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

getField :: Parameter a -> 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 #

Methods

from1 :: forall (a :: k). Parameter a -> Rep1 Parameter a #

to1 :: forall (a :: k). Rep1 Parameter a -> Parameter a #

type Rep (Parameter a) Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep (Parameter a) = D1 ('MetaData "Parameter" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'True) (C1 ('MetaCons "Parameter" 'PrefixI 'True) (S1 ('MetaSel ('Just "getParameter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (((DefaultParameter :+: (DictionarySplat :+: Identifier)) :+: ((ListSplat :+: Tuple) :+: (TypedDefaultParameter :+: TypedParameter))) a))))
type Rep1 Parameter Source # 
Instance details

Defined in TreeSitter.Python.AST

type Rep1 Parameter = D1 ('MetaData "Parameter" "TreeSitter.Python.AST" "tree-sitter-python-0.8.1.0-inplace" 'True) (C1 ('MetaCons "Parameter" 'PrefixI 'True) (S1 ('MetaSel ('Just "getParameter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 ((DefaultParameter :+: (DictionarySplat :+: Identifier)) :+: ((ListSplat :+: Tuple) :+: (TypedDefaultParameter :+: TypedParameter))))))

newtype Expression a Source #

Instances

Instances details
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 #

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

matchers' :: IntMap (Match Expression)

matchers :: B (Int, Match Expression)

HasField "ann" (Expression a) a Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

getField :: Expression a -> 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 #

Methods

from1 :: forall (a :: k). Expression a -> Rep1 Expression a #

to1 :: forall (a :: k). Rep1 Expression a -> Expression a #

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.8.1.0-inplace" 'True) (C1 ('MetaCons "Expression" 'PrefixI 'True) (S1 ('MetaSel ('Just "getExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((((PrimaryExpression :+: Await) :+: (BooleanOperator :+: ComparisonOperator)) :+: ((ConditionalExpression :+: Lambda) :+: (NamedExpression :+: 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.8.1.0-inplace" 'True) (C1 ('MetaCons "Expression" 'PrefixI 'True) (S1 ('MetaSel ('Just "getExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (((PrimaryExpression :+: Await) :+: (BooleanOperator :+: ComparisonOperator)) :+: ((ConditionalExpression :+: Lambda) :+: (NamedExpression :+: NotOperator))))))

newtype CompoundStatement a Source #

Instances

Instances details
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 #

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

HasField "ann" (CompoundStatement a) a Source # 
Instance details

Defined in TreeSitter.Python.AST

Methods

getField :: CompoundStatement a -> 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 #

Methods

from1 :: forall (a :: k). CompoundStatement a -> Rep1 CompoundStatement a #

to1 :: forall (a :: k). Rep1 CompoundStatement a -> CompoundStatement a #

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.8.1.0-inplace" 'True) (C1 ('MetaCons "CompoundStatement" 'PrefixI 'True) (S1 ('MetaSel ('Just "getCompoundStatement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((((ClassDefinition :+: DecoratedDefinition) :+: (ForStatement :+: FunctionDefinition)) :+: ((IfStatement :+: TryStatement) :+: (WhileStatement :+: 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.8.1.0-inplace" 'True) (C1 ('MetaCons "CompoundStatement" 'PrefixI 'True) (S1 ('MetaSel ('Just "getCompoundStatement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (((ClassDefinition :+: DecoratedDefinition) :+: (ForStatement :+: FunctionDefinition)) :+: ((IfStatement :+: TryStatement) :+: (WhileStatement :+: WithStatement))))))