language-python-0.5.6: Parsing and pretty printing of Python code.

Copyright(c) 2009 Bernie Pope
LicenseBSD-style
Maintainerbjpop@csse.unimelb.edu.au
Stabilityexperimental
Portabilityghc
Safe HaskellSafe
LanguageHaskell98

Language.Python.Common.AST

Contents

Description

Representation of the Python abstract syntax tree (AST). The representation is a superset of versions 2.x and 3.x of Python. In many cases they are identical. The documentation in this module indicates where they are different.

All the data types have a (polymorphic) parameter which allows the AST to be annotated by an arbitrary type (for example source locations). Specialised instances of the types are provided for source spans. For example Module a is the type of modules, and ModuleSpan is the type of modules annoted with source span information.

Note: there are cases where the AST is more liberal than the formal grammar of the language. Therefore some care must be taken when constructing Python programs using the raw AST.

Synopsis

Annotation projection

class Annotated t where Source #

Convenient access to annotations in annotated types.

Methods

annot :: t annot -> annot Source #

Given an annotated type, project out its annotation value.

Instances
Annotated AssignOp Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: AssignOp annot -> annot Source #

Annotated Op Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Op annot -> annot Source #

Annotated Slice Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Slice annot -> annot Source #

Annotated Expr Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Expr annot -> annot Source #

Annotated CompIter Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: CompIter annot -> annot Source #

Annotated CompIf Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: CompIf annot -> annot Source #

Annotated CompFor Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: CompFor annot -> annot Source #

Annotated Comprehension Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Comprehension annot -> annot Source #

Annotated ExceptClause Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: ExceptClause annot -> annot Source #

Annotated Handler Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Handler annot -> annot Source #

Annotated Argument Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Argument annot -> annot Source #

Annotated ParamTuple Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: ParamTuple annot -> annot Source #

Annotated Parameter Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Parameter annot -> annot Source #

Annotated Decorator Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Decorator annot -> annot Source #

Annotated Statement Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Statement annot -> annot Source #

Annotated ImportRelative Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: ImportRelative annot -> annot Source #

Annotated FromItems Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: FromItems annot -> annot Source #

Annotated FromItem Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: FromItem annot -> annot Source #

Annotated ImportItem Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: ImportItem annot -> annot Source #

Annotated Ident Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Ident annot -> annot Source #

Modules

newtype Module annot Source #

Constructors

Module [Statement annot]

A module is just a sequence of top-level statements.

Instances
Functor Module Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> Module a -> Module b Source #

(<$) :: a -> Module b -> Module a Source #

Eq annot => Eq (Module annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: Module annot -> Module annot -> Bool Source #

(/=) :: Module annot -> Module annot -> Bool Source #

Data annot => Data (Module annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module annot -> c (Module annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Module annot) Source #

toConstr :: Module annot -> Constr Source #

dataTypeOf :: Module annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Module annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Module annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> Module annot -> Module annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Module annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Module annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module annot -> m (Module annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module annot -> m (Module annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module annot -> m (Module annot) Source #

Ord annot => Ord (Module annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: Module annot -> Module annot -> Ordering Source #

(<) :: Module annot -> Module annot -> Bool Source #

(<=) :: Module annot -> Module annot -> Bool Source #

(>) :: Module annot -> Module annot -> Bool Source #

(>=) :: Module annot -> Module annot -> Bool Source #

max :: Module annot -> Module annot -> Module annot Source #

min :: Module annot -> Module annot -> Module annot Source #

Show annot => Show (Module annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> Module annot -> ShowS Source #

show :: Module annot -> String Source #

showList :: [Module annot] -> ShowS Source #

Pretty (Module a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: Module a -> Doc Source #

Identifiers and dotted names

data Ident annot Source #

Identifier.

Constructors

Ident 

Fields

Instances
Functor Ident Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> Ident a -> Ident b Source #

(<$) :: a -> Ident b -> Ident a Source #

Span IdentSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated Ident Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Ident annot -> annot Source #

Eq annot => Eq (Ident annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: Ident annot -> Ident annot -> Bool Source #

(/=) :: Ident annot -> Ident annot -> Bool Source #

Data annot => Data (Ident annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ident annot -> c (Ident annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ident annot) Source #

toConstr :: Ident annot -> Constr Source #

dataTypeOf :: Ident annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ident annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ident annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> Ident annot -> Ident annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Ident annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ident annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ident annot -> m (Ident annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident annot -> m (Ident annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident annot -> m (Ident annot) Source #

Ord annot => Ord (Ident annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: Ident annot -> Ident annot -> Ordering Source #

(<) :: Ident annot -> Ident annot -> Bool Source #

(<=) :: Ident annot -> Ident annot -> Bool Source #

(>) :: Ident annot -> Ident annot -> Bool Source #

(>=) :: Ident annot -> Ident annot -> Bool Source #

max :: Ident annot -> Ident annot -> Ident annot Source #

min :: Ident annot -> Ident annot -> Ident annot Source #

Show annot => Show (Ident annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> Ident annot -> ShowS Source #

show :: Ident annot -> String Source #

showList :: [Ident annot] -> ShowS Source #

Pretty (Ident a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: Ident a -> Doc Source #

type DottedName annot = [Ident annot] Source #

A compound name constructed with the dot operator.

Statements, suites, parameters, decorators and assignment operators

data Statement annot Source #

Constructors

Import

Import statement.

Fields

FromImport

From ... import statement.

Fields

While

While loop.

Fields

For

For loop.

Fields

AsyncFor 

Fields

Fun

Function definition.

Fields

AsyncFun 

Fields

Class

Class definition.

Fields

Conditional

Conditional statement (if-elif-else).

Fields

Assign

Assignment statement.

Fields

AugmentedAssign

Augmented assignment statement.

Fields

AnnotatedAssign 

Fields

Decorated

Decorated definition of a function or class.

Fields

Return

Return statement (may only occur syntactically nested in a function definition).

Fields

Try

Try statement (exception handling).

Fields

Raise

Raise statement (exception throwing).

Fields

With

With statement (context management).

Fields

AsyncWith 

Fields

Pass

Pass statement (null operation).

Fields

Break

Break statement (may only occur syntactically nested in a for or while loop, but not nested in a function or class definition within that loop).

Fields

Continue

Continue statement (may only occur syntactically nested in a for or while loop, but not nested in a function or class definition or finally clause within that loop).

Fields

Delete

Del statement (delete).

Fields

StmtExpr

Expression statement.

Fields

Global

Global declaration.

Fields

NonLocal

Nonlocal declaration. Version 3.x only.

Fields

  • nonLocal_vars :: [Ident annot]

    Variables declared nonlocal in the current block (their binding comes from bound the nearest enclosing scope).

  • stmt_annot :: annot
     
Assert

Assertion.

Fields

Print

Print statement. Version 2 only.

Fields

Exec

Exec statement. Version 2 only.

Fields

Instances
Functor Statement Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> Statement a -> Statement b Source #

(<$) :: a -> Statement b -> Statement a Source #

Span StatementSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated Statement Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Statement annot -> annot Source #

Eq annot => Eq (Statement annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: Statement annot -> Statement annot -> Bool Source #

(/=) :: Statement annot -> Statement annot -> Bool Source #

Data annot => Data (Statement annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Statement annot -> c (Statement annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Statement annot) Source #

toConstr :: Statement annot -> Constr Source #

dataTypeOf :: Statement annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Statement annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Statement annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> Statement annot -> Statement annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Statement annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Statement annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Statement annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Statement annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Statement annot -> m (Statement annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Statement annot -> m (Statement annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Statement annot -> m (Statement annot) Source #

Ord annot => Ord (Statement annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: Statement annot -> Statement annot -> Ordering Source #

(<) :: Statement annot -> Statement annot -> Bool Source #

(<=) :: Statement annot -> Statement annot -> Bool Source #

(>) :: Statement annot -> Statement annot -> Bool Source #

(>=) :: Statement annot -> Statement annot -> Bool Source #

max :: Statement annot -> Statement annot -> Statement annot Source #

min :: Statement annot -> Statement annot -> Statement annot Source #

Show annot => Show (Statement annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> Statement annot -> ShowS Source #

show :: Statement annot -> String Source #

showList :: [Statement annot] -> ShowS Source #

Pretty (Statement a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: Statement a -> Doc Source #

type Suite annot = [Statement annot] Source #

A block of statements. A suite is a group of statements controlled by a clause, for example, the body of a loop.

data Parameter annot Source #

Constructors

Param

Ordinary named parameter.

Fields

VarArgsPos

Excess positional parameter (single asterisk before its name in the concrete syntax).

Fields

VarArgsKeyword

Excess keyword parameter (double asterisk before its name in the concrete syntax).

Fields

EndPositional

Marker for the end of positional parameters (not a parameter itself).

Fields

UnPackTuple

Tuple unpack. Version 2 only.

Fields

Instances
Functor Parameter Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> Parameter a -> Parameter b Source #

(<$) :: a -> Parameter b -> Parameter a Source #

Span ParameterSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated Parameter Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Parameter annot -> annot Source #

Eq annot => Eq (Parameter annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: Parameter annot -> Parameter annot -> Bool Source #

(/=) :: Parameter annot -> Parameter annot -> Bool Source #

Data annot => Data (Parameter annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Parameter annot -> c (Parameter annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Parameter annot) Source #

toConstr :: Parameter annot -> Constr Source #

dataTypeOf :: Parameter annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Parameter annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Parameter annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> Parameter annot -> Parameter annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parameter annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parameter annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Parameter annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Parameter annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Parameter annot -> m (Parameter annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Parameter annot -> m (Parameter annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Parameter annot -> m (Parameter annot) Source #

Ord annot => Ord (Parameter annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: Parameter annot -> Parameter annot -> Ordering Source #

(<) :: Parameter annot -> Parameter annot -> Bool Source #

(<=) :: Parameter annot -> Parameter annot -> Bool Source #

(>) :: Parameter annot -> Parameter annot -> Bool Source #

(>=) :: Parameter annot -> Parameter annot -> Bool Source #

max :: Parameter annot -> Parameter annot -> Parameter annot Source #

min :: Parameter annot -> Parameter annot -> Parameter annot Source #

Show annot => Show (Parameter annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> Parameter annot -> ShowS Source #

show :: Parameter annot -> String Source #

showList :: [Parameter annot] -> ShowS Source #

Pretty (Parameter a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: Parameter a -> Doc Source #

data ParamTuple annot Source #

Tuple unpack parameter. Version 2 only.

Constructors

ParamTupleName

A variable name.

Fields

ParamTuple

A (possibly nested) tuple parameter.

Fields

Instances
Functor ParamTuple Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> ParamTuple a -> ParamTuple b Source #

(<$) :: a -> ParamTuple b -> ParamTuple a Source #

Span ParamTupleSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated ParamTuple Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: ParamTuple annot -> annot Source #

Eq annot => Eq (ParamTuple annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: ParamTuple annot -> ParamTuple annot -> Bool Source #

(/=) :: ParamTuple annot -> ParamTuple annot -> Bool Source #

Data annot => Data (ParamTuple annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParamTuple annot -> c (ParamTuple annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParamTuple annot) Source #

toConstr :: ParamTuple annot -> Constr Source #

dataTypeOf :: ParamTuple annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParamTuple annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParamTuple annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> ParamTuple annot -> ParamTuple annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParamTuple annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParamTuple annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ParamTuple annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParamTuple annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParamTuple annot -> m (ParamTuple annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamTuple annot -> m (ParamTuple annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamTuple annot -> m (ParamTuple annot) Source #

Ord annot => Ord (ParamTuple annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: ParamTuple annot -> ParamTuple annot -> Ordering Source #

(<) :: ParamTuple annot -> ParamTuple annot -> Bool Source #

(<=) :: ParamTuple annot -> ParamTuple annot -> Bool Source #

(>) :: ParamTuple annot -> ParamTuple annot -> Bool Source #

(>=) :: ParamTuple annot -> ParamTuple annot -> Bool Source #

max :: ParamTuple annot -> ParamTuple annot -> ParamTuple annot Source #

min :: ParamTuple annot -> ParamTuple annot -> ParamTuple annot Source #

Show annot => Show (ParamTuple annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> ParamTuple annot -> ShowS Source #

show :: ParamTuple annot -> String Source #

showList :: [ParamTuple annot] -> ShowS Source #

Pretty (ParamTuple a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: ParamTuple a -> Doc Source #

data Decorator annot Source #

Decorator.

Constructors

Decorator 

Fields

Instances
Functor Decorator Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> Decorator a -> Decorator b Source #

(<$) :: a -> Decorator b -> Decorator a Source #

Span DecoratorSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated Decorator Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Decorator annot -> annot Source #

Eq annot => Eq (Decorator annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: Decorator annot -> Decorator annot -> Bool Source #

(/=) :: Decorator annot -> Decorator annot -> Bool Source #

Data annot => Data (Decorator annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Decorator annot -> c (Decorator annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Decorator annot) Source #

toConstr :: Decorator annot -> Constr Source #

dataTypeOf :: Decorator annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Decorator annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Decorator annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> Decorator annot -> Decorator annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Decorator annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Decorator annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Decorator annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Decorator annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Decorator annot -> m (Decorator annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Decorator annot -> m (Decorator annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Decorator annot -> m (Decorator annot) Source #

Ord annot => Ord (Decorator annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: Decorator annot -> Decorator annot -> Ordering Source #

(<) :: Decorator annot -> Decorator annot -> Bool Source #

(<=) :: Decorator annot -> Decorator annot -> Bool Source #

(>) :: Decorator annot -> Decorator annot -> Bool Source #

(>=) :: Decorator annot -> Decorator annot -> Bool Source #

max :: Decorator annot -> Decorator annot -> Decorator annot Source #

min :: Decorator annot -> Decorator annot -> Decorator annot Source #

Show annot => Show (Decorator annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> Decorator annot -> ShowS Source #

show :: Decorator annot -> String Source #

showList :: [Decorator annot] -> ShowS Source #

Pretty (Decorator a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: Decorator a -> Doc Source #

data AssignOp annot Source #

Augmented assignment operators.

Constructors

PlusAssign

'+='

Fields

MinusAssign

'-='

Fields

MultAssign

'*='

Fields

DivAssign

'/='

Fields

ModAssign

'%='

Fields

PowAssign

'*='

Fields

BinAndAssign

'&='

Fields

BinOrAssign

'|='

Fields

BinXorAssign

'^='

Fields

LeftShiftAssign

'<<='

Fields

RightShiftAssign

'>>='

Fields

FloorDivAssign

'//='

Fields

MatrixMultAssign

'@='

Fields

Instances
Functor AssignOp Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> AssignOp a -> AssignOp b Source #

(<$) :: a -> AssignOp b -> AssignOp a Source #

Span AssignOpSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated AssignOp Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: AssignOp annot -> annot Source #

Eq annot => Eq (AssignOp annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: AssignOp annot -> AssignOp annot -> Bool Source #

(/=) :: AssignOp annot -> AssignOp annot -> Bool Source #

Data annot => Data (AssignOp annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AssignOp annot -> c (AssignOp annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AssignOp annot) Source #

toConstr :: AssignOp annot -> Constr Source #

dataTypeOf :: AssignOp annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AssignOp annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AssignOp annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> AssignOp annot -> AssignOp annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AssignOp annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AssignOp annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> AssignOp annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AssignOp annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AssignOp annot -> m (AssignOp annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AssignOp annot -> m (AssignOp annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AssignOp annot -> m (AssignOp annot) Source #

Ord annot => Ord (AssignOp annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: AssignOp annot -> AssignOp annot -> Ordering Source #

(<) :: AssignOp annot -> AssignOp annot -> Bool Source #

(<=) :: AssignOp annot -> AssignOp annot -> Bool Source #

(>) :: AssignOp annot -> AssignOp annot -> Bool Source #

(>=) :: AssignOp annot -> AssignOp annot -> Bool Source #

max :: AssignOp annot -> AssignOp annot -> AssignOp annot Source #

min :: AssignOp annot -> AssignOp annot -> AssignOp annot Source #

Show annot => Show (AssignOp annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> AssignOp annot -> ShowS Source #

show :: AssignOp annot -> String Source #

showList :: [AssignOp annot] -> ShowS Source #

Pretty (AssignOp a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: AssignOp a -> Doc Source #

Expressions, operators, arguments and slices

data Expr annot Source #

Constructors

Var

Variable.

Fields

Int

Literal integer.

LongInt

Long literal integer. Version 2 only.

Float

Literal floating point number.

Imaginary

Literal imaginary number.

Bool

Literal boolean.

Fields

None

Literal 'None' value.

Fields

Ellipsis

Ellipsis '...'.

Fields

ByteStrings

Literal byte string.

Fields

Strings

Literal strings (to be concatentated together).

Fields

UnicodeStrings

Unicode literal strings (to be concatentated together). Version 2 only.

Call

Function call.

Fields

Subscript

Subscription, for example 'x [y]'.

Fields

SlicedExpr

Slicing, for example 'w [x:y:z]'.

Fields

CondExpr

Conditional expresison.

Fields

BinaryOp

Binary operator application.

Fields

UnaryOp

Unary operator application.

Fields

Dot 

Fields

Lambda

Anonymous function definition (lambda).

Fields

Tuple

Tuple. Can be empty.

Fields

Yield

Generator yield.

Fields

Generator

Generator.

Fields

Await

Await

Fields

ListComp

List comprehension.

Fields

List

List.

Fields

Dictionary

Dictionary.

Fields

DictComp

Dictionary comprehension. Version 3 only.

Fields

Set

Set.

Fields

SetComp

Set comprehension. Version 3 only.

Fields

Starred

Starred expression. Version 3 only.

Fields

Paren

Parenthesised expression.

Fields

StringConversion

String conversion (backquoted expression). Version 2 only.

Fields

Instances
Functor Expr Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> Expr a -> Expr b Source #

(<$) :: a -> Expr b -> Expr a Source #

Span ExprSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated Expr Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Expr annot -> annot Source #

Eq annot => Eq (Expr annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: Expr annot -> Expr annot -> Bool Source #

(/=) :: Expr annot -> Expr annot -> Bool Source #

Data annot => Data (Expr annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Expr annot -> c (Expr annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Expr annot) Source #

toConstr :: Expr annot -> Constr Source #

dataTypeOf :: Expr annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Expr annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Expr annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> Expr annot -> Expr annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Expr annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Expr annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Expr annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Expr annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Expr annot -> m (Expr annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr annot -> m (Expr annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr annot -> m (Expr annot) Source #

Ord annot => Ord (Expr annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: Expr annot -> Expr annot -> Ordering Source #

(<) :: Expr annot -> Expr annot -> Bool Source #

(<=) :: Expr annot -> Expr annot -> Bool Source #

(>) :: Expr annot -> Expr annot -> Bool Source #

(>=) :: Expr annot -> Expr annot -> Bool Source #

max :: Expr annot -> Expr annot -> Expr annot Source #

min :: Expr annot -> Expr annot -> Expr annot Source #

Show annot => Show (Expr annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> Expr annot -> ShowS Source #

show :: Expr annot -> String Source #

showList :: [Expr annot] -> ShowS Source #

Pretty (Expr a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: Expr a -> Doc Source #

data Op annot Source #

Operators.

Constructors

And

'and'

Fields

Or

'or'

Fields

Not

'not'

Fields

Exponent

'**'

Fields

LessThan

'<'

Fields

GreaterThan

'>'

Fields

Equality

'=='

Fields

GreaterThanEquals

'>='

Fields

LessThanEquals

'<='

Fields

NotEquals

'!='

Fields

NotEqualsV2

'<>'. Version 2 only.

Fields

In

'in'

Fields

Is

'is'

Fields

IsNot

'is not'

Fields

NotIn

'not in'

Fields

BinaryOr

'|'

Fields

Xor

'^'

Fields

BinaryAnd

'&'

Fields

ShiftLeft

'<<'

Fields

ShiftRight

'>>'

Fields

Multiply

'*'

Fields

Plus

'+'

Fields

Minus

'-'

Fields

Divide

'/'

Fields

FloorDivide

'//'

Fields

MatrixMult

'@'

Fields

Invert

'~' (bitwise inversion of its integer argument)

Fields

Modulo

'%'

Fields

Instances
Functor Op Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> Op a -> Op b Source #

(<$) :: a -> Op b -> Op a Source #

Span OpSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated Op Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Op annot -> annot Source #

Eq annot => Eq (Op annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: Op annot -> Op annot -> Bool Source #

(/=) :: Op annot -> Op annot -> Bool Source #

Data annot => Data (Op annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Op annot -> c (Op annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Op annot) Source #

toConstr :: Op annot -> Constr Source #

dataTypeOf :: Op annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Op annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Op annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> Op annot -> Op annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Op annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Op annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Op annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Op annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Op annot -> m (Op annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Op annot -> m (Op annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Op annot -> m (Op annot) Source #

Ord annot => Ord (Op annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: Op annot -> Op annot -> Ordering Source #

(<) :: Op annot -> Op annot -> Bool Source #

(<=) :: Op annot -> Op annot -> Bool Source #

(>) :: Op annot -> Op annot -> Bool Source #

(>=) :: Op annot -> Op annot -> Bool Source #

max :: Op annot -> Op annot -> Op annot Source #

min :: Op annot -> Op annot -> Op annot Source #

Show annot => Show (Op annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> Op annot -> ShowS Source #

show :: Op annot -> String Source #

showList :: [Op annot] -> ShowS Source #

Pretty (Op a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: Op a -> Doc Source #

data Argument annot Source #

Arguments to function calls, class declarations and decorators.

Constructors

ArgExpr

Ordinary argument expression.

Fields

ArgVarArgsPos

Excess positional argument.

Fields

ArgVarArgsKeyword

Excess keyword argument.

Fields

ArgKeyword

Keyword argument.

Fields

Instances
Functor Argument Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> Argument a -> Argument b Source #

(<$) :: a -> Argument b -> Argument a Source #

Span ArgumentSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated Argument Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Argument annot -> annot Source #

Eq annot => Eq (Argument annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: Argument annot -> Argument annot -> Bool Source #

(/=) :: Argument annot -> Argument annot -> Bool Source #

Data annot => Data (Argument annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Argument annot -> c (Argument annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Argument annot) Source #

toConstr :: Argument annot -> Constr Source #

dataTypeOf :: Argument annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Argument annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Argument annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> Argument annot -> Argument annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Argument annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Argument annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Argument annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Argument annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Argument annot -> m (Argument annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Argument annot -> m (Argument annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Argument annot -> m (Argument annot) Source #

Ord annot => Ord (Argument annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: Argument annot -> Argument annot -> Ordering Source #

(<) :: Argument annot -> Argument annot -> Bool Source #

(<=) :: Argument annot -> Argument annot -> Bool Source #

(>) :: Argument annot -> Argument annot -> Bool Source #

(>=) :: Argument annot -> Argument annot -> Bool Source #

max :: Argument annot -> Argument annot -> Argument annot Source #

min :: Argument annot -> Argument annot -> Argument annot Source #

Show annot => Show (Argument annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> Argument annot -> ShowS Source #

show :: Argument annot -> String Source #

showList :: [Argument annot] -> ShowS Source #

Pretty (Argument a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: Argument a -> Doc Source #

data Slice annot Source #

Slice compenent.

Constructors

SliceProper 

Fields

SliceExpr 

Fields

SliceEllipsis 

Fields

Instances
Functor Slice Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> Slice a -> Slice b Source #

(<$) :: a -> Slice b -> Slice a Source #

Span SliceSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated Slice Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Slice annot -> annot Source #

Eq annot => Eq (Slice annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: Slice annot -> Slice annot -> Bool Source #

(/=) :: Slice annot -> Slice annot -> Bool Source #

Data annot => Data (Slice annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Slice annot -> c (Slice annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Slice annot) Source #

toConstr :: Slice annot -> Constr Source #

dataTypeOf :: Slice annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Slice annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Slice annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> Slice annot -> Slice annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Slice annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Slice annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Slice annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Slice annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Slice annot -> m (Slice annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Slice annot -> m (Slice annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Slice annot -> m (Slice annot) Source #

Ord annot => Ord (Slice annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: Slice annot -> Slice annot -> Ordering Source #

(<) :: Slice annot -> Slice annot -> Bool Source #

(<=) :: Slice annot -> Slice annot -> Bool Source #

(>) :: Slice annot -> Slice annot -> Bool Source #

(>=) :: Slice annot -> Slice annot -> Bool Source #

max :: Slice annot -> Slice annot -> Slice annot Source #

min :: Slice annot -> Slice annot -> Slice annot Source #

Show annot => Show (Slice annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> Slice annot -> ShowS Source #

show :: Slice annot -> String Source #

showList :: [Slice annot] -> ShowS Source #

Pretty (Slice a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: Slice a -> Doc Source #

data DictKeyDatumList annot Source #

Constructors

DictMappingPair (Expr annot) (Expr annot) 
DictUnpacking (Expr annot) 
Instances
Functor DictKeyDatumList Source # 
Instance details

Defined in Language.Python.Common.AST

Span DictKeyDatumListSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Eq annot => Eq (DictKeyDatumList annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Data annot => Data (DictKeyDatumList annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DictKeyDatumList annot -> c (DictKeyDatumList annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DictKeyDatumList annot) Source #

toConstr :: DictKeyDatumList annot -> Constr Source #

dataTypeOf :: DictKeyDatumList annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DictKeyDatumList annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DictKeyDatumList annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> DictKeyDatumList annot -> DictKeyDatumList annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DictKeyDatumList annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DictKeyDatumList annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DictKeyDatumList annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DictKeyDatumList annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DictKeyDatumList annot -> m (DictKeyDatumList annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DictKeyDatumList annot -> m (DictKeyDatumList annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DictKeyDatumList annot -> m (DictKeyDatumList annot) Source #

Ord annot => Ord (DictKeyDatumList annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Show annot => Show (DictKeyDatumList annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Pretty (DictKeyDatumList a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

data YieldArg annot Source #

Constructors

YieldFrom (Expr annot) annot

Yield from a generator (Version 3 only)

YieldExpr (Expr annot)

Yield value of an expression

Instances
Functor YieldArg Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> YieldArg a -> YieldArg b Source #

(<$) :: a -> YieldArg b -> YieldArg a Source #

Span YieldArgSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Eq annot => Eq (YieldArg annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: YieldArg annot -> YieldArg annot -> Bool Source #

(/=) :: YieldArg annot -> YieldArg annot -> Bool Source #

Data annot => Data (YieldArg annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> YieldArg annot -> c (YieldArg annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (YieldArg annot) Source #

toConstr :: YieldArg annot -> Constr Source #

dataTypeOf :: YieldArg annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (YieldArg annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (YieldArg annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> YieldArg annot -> YieldArg annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> YieldArg annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> YieldArg annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> YieldArg annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> YieldArg annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> YieldArg annot -> m (YieldArg annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> YieldArg annot -> m (YieldArg annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> YieldArg annot -> m (YieldArg annot) Source #

Ord annot => Ord (YieldArg annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: YieldArg annot -> YieldArg annot -> Ordering Source #

(<) :: YieldArg annot -> YieldArg annot -> Bool Source #

(<=) :: YieldArg annot -> YieldArg annot -> Bool Source #

(>) :: YieldArg annot -> YieldArg annot -> Bool Source #

(>=) :: YieldArg annot -> YieldArg annot -> Bool Source #

max :: YieldArg annot -> YieldArg annot -> YieldArg annot Source #

min :: YieldArg annot -> YieldArg annot -> YieldArg annot Source #

Show annot => Show (YieldArg annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> YieldArg annot -> ShowS Source #

show :: YieldArg annot -> String Source #

showList :: [YieldArg annot] -> ShowS Source #

Pretty (YieldArg a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: YieldArg a -> Doc Source #

Imports

data ImportItem annot Source #

Constructors

ImportItem 

Fields

Instances
Functor ImportItem Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> ImportItem a -> ImportItem b Source #

(<$) :: a -> ImportItem b -> ImportItem a Source #

Span ImportItemSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated ImportItem Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: ImportItem annot -> annot Source #

Eq annot => Eq (ImportItem annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: ImportItem annot -> ImportItem annot -> Bool Source #

(/=) :: ImportItem annot -> ImportItem annot -> Bool Source #

Data annot => Data (ImportItem annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportItem annot -> c (ImportItem annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportItem annot) Source #

toConstr :: ImportItem annot -> Constr Source #

dataTypeOf :: ImportItem annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportItem annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportItem annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportItem annot -> ImportItem annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportItem annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportItem annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportItem annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportItem annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportItem annot -> m (ImportItem annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportItem annot -> m (ImportItem annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportItem annot -> m (ImportItem annot) Source #

Ord annot => Ord (ImportItem annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: ImportItem annot -> ImportItem annot -> Ordering Source #

(<) :: ImportItem annot -> ImportItem annot -> Bool Source #

(<=) :: ImportItem annot -> ImportItem annot -> Bool Source #

(>) :: ImportItem annot -> ImportItem annot -> Bool Source #

(>=) :: ImportItem annot -> ImportItem annot -> Bool Source #

max :: ImportItem annot -> ImportItem annot -> ImportItem annot Source #

min :: ImportItem annot -> ImportItem annot -> ImportItem annot Source #

Show annot => Show (ImportItem annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> ImportItem annot -> ShowS Source #

show :: ImportItem annot -> String Source #

showList :: [ImportItem annot] -> ShowS Source #

Pretty (ImportItem a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: ImportItem a -> Doc Source #

data FromItem annot Source #

Constructors

FromItem 

Fields

Instances
Functor FromItem Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> FromItem a -> FromItem b Source #

(<$) :: a -> FromItem b -> FromItem a Source #

Span FromItemSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated FromItem Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: FromItem annot -> annot Source #

Eq annot => Eq (FromItem annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: FromItem annot -> FromItem annot -> Bool Source #

(/=) :: FromItem annot -> FromItem annot -> Bool Source #

Data annot => Data (FromItem annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FromItem annot -> c (FromItem annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromItem annot) Source #

toConstr :: FromItem annot -> Constr Source #

dataTypeOf :: FromItem annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FromItem annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromItem annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> FromItem annot -> FromItem annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromItem annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromItem annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FromItem annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromItem annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromItem annot -> m (FromItem annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromItem annot -> m (FromItem annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromItem annot -> m (FromItem annot) Source #

Ord annot => Ord (FromItem annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: FromItem annot -> FromItem annot -> Ordering Source #

(<) :: FromItem annot -> FromItem annot -> Bool Source #

(<=) :: FromItem annot -> FromItem annot -> Bool Source #

(>) :: FromItem annot -> FromItem annot -> Bool Source #

(>=) :: FromItem annot -> FromItem annot -> Bool Source #

max :: FromItem annot -> FromItem annot -> FromItem annot Source #

min :: FromItem annot -> FromItem annot -> FromItem annot Source #

Show annot => Show (FromItem annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> FromItem annot -> ShowS Source #

show :: FromItem annot -> String Source #

showList :: [FromItem annot] -> ShowS Source #

Pretty (FromItem a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: FromItem a -> Doc Source #

data FromItems annot Source #

Items imported using the 'from ... import' construct.

Constructors

ImportEverything

Import everything exported from the module.

Fields

FromItems

Import a specific list of items from the module.

Fields

Instances
Functor FromItems Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> FromItems a -> FromItems b Source #

(<$) :: a -> FromItems b -> FromItems a Source #

Span FromItemsSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated FromItems Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: FromItems annot -> annot Source #

Eq annot => Eq (FromItems annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: FromItems annot -> FromItems annot -> Bool Source #

(/=) :: FromItems annot -> FromItems annot -> Bool Source #

Data annot => Data (FromItems annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FromItems annot -> c (FromItems annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromItems annot) Source #

toConstr :: FromItems annot -> Constr Source #

dataTypeOf :: FromItems annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FromItems annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromItems annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> FromItems annot -> FromItems annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromItems annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromItems annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FromItems annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromItems annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromItems annot -> m (FromItems annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromItems annot -> m (FromItems annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromItems annot -> m (FromItems annot) Source #

Ord annot => Ord (FromItems annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: FromItems annot -> FromItems annot -> Ordering Source #

(<) :: FromItems annot -> FromItems annot -> Bool Source #

(<=) :: FromItems annot -> FromItems annot -> Bool Source #

(>) :: FromItems annot -> FromItems annot -> Bool Source #

(>=) :: FromItems annot -> FromItems annot -> Bool Source #

max :: FromItems annot -> FromItems annot -> FromItems annot Source #

min :: FromItems annot -> FromItems annot -> FromItems annot Source #

Show annot => Show (FromItems annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> FromItems annot -> ShowS Source #

show :: FromItems annot -> String Source #

showList :: [FromItems annot] -> ShowS Source #

Pretty (FromItems a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: FromItems a -> Doc Source #

data ImportRelative annot Source #

A reference to the module to import from using the 'from ... import' construct.

Instances
Functor ImportRelative Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> ImportRelative a -> ImportRelative b Source #

(<$) :: a -> ImportRelative b -> ImportRelative a Source #

Span ImportRelativeSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated ImportRelative Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: ImportRelative annot -> annot Source #

Eq annot => Eq (ImportRelative annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: ImportRelative annot -> ImportRelative annot -> Bool Source #

(/=) :: ImportRelative annot -> ImportRelative annot -> Bool Source #

Data annot => Data (ImportRelative annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportRelative annot -> c (ImportRelative annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportRelative annot) Source #

toConstr :: ImportRelative annot -> Constr Source #

dataTypeOf :: ImportRelative annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportRelative annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportRelative annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportRelative annot -> ImportRelative annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportRelative annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportRelative annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportRelative annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportRelative annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportRelative annot -> m (ImportRelative annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportRelative annot -> m (ImportRelative annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportRelative annot -> m (ImportRelative annot) Source #

Ord annot => Ord (ImportRelative annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Show annot => Show (ImportRelative annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Pretty (ImportRelative a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Exceptions

data Handler annot Source #

Exception handler.

Constructors

Handler 

Fields

Instances
Functor Handler Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> Handler a -> Handler b Source #

(<$) :: a -> Handler b -> Handler a Source #

Span HandlerSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated Handler Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Handler annot -> annot Source #

Eq annot => Eq (Handler annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: Handler annot -> Handler annot -> Bool Source #

(/=) :: Handler annot -> Handler annot -> Bool Source #

Data annot => Data (Handler annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Handler annot -> c (Handler annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Handler annot) Source #

toConstr :: Handler annot -> Constr Source #

dataTypeOf :: Handler annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Handler annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Handler annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> Handler annot -> Handler annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Handler annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Handler annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Handler annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Handler annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Handler annot -> m (Handler annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Handler annot -> m (Handler annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Handler annot -> m (Handler annot) Source #

Ord annot => Ord (Handler annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: Handler annot -> Handler annot -> Ordering Source #

(<) :: Handler annot -> Handler annot -> Bool Source #

(<=) :: Handler annot -> Handler annot -> Bool Source #

(>) :: Handler annot -> Handler annot -> Bool Source #

(>=) :: Handler annot -> Handler annot -> Bool Source #

max :: Handler annot -> Handler annot -> Handler annot Source #

min :: Handler annot -> Handler annot -> Handler annot Source #

Show annot => Show (Handler annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> Handler annot -> ShowS Source #

show :: Handler annot -> String Source #

showList :: [Handler annot] -> ShowS Source #

Pretty (Handler a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: Handler a -> Doc Source #

data ExceptClause annot Source #

Exception clause.

Constructors

ExceptClause 

Fields

Instances
Functor ExceptClause Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> ExceptClause a -> ExceptClause b Source #

(<$) :: a -> ExceptClause b -> ExceptClause a Source #

Span ExceptClauseSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated ExceptClause Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: ExceptClause annot -> annot Source #

Eq annot => Eq (ExceptClause annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: ExceptClause annot -> ExceptClause annot -> Bool Source #

(/=) :: ExceptClause annot -> ExceptClause annot -> Bool Source #

Data annot => Data (ExceptClause annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExceptClause annot -> c (ExceptClause annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ExceptClause annot) Source #

toConstr :: ExceptClause annot -> Constr Source #

dataTypeOf :: ExceptClause annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ExceptClause annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ExceptClause annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> ExceptClause annot -> ExceptClause annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExceptClause annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExceptClause annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ExceptClause annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExceptClause annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExceptClause annot -> m (ExceptClause annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExceptClause annot -> m (ExceptClause annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExceptClause annot -> m (ExceptClause annot) Source #

Ord annot => Ord (ExceptClause annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: ExceptClause annot -> ExceptClause annot -> Ordering Source #

(<) :: ExceptClause annot -> ExceptClause annot -> Bool Source #

(<=) :: ExceptClause annot -> ExceptClause annot -> Bool Source #

(>) :: ExceptClause annot -> ExceptClause annot -> Bool Source #

(>=) :: ExceptClause annot -> ExceptClause annot -> Bool Source #

max :: ExceptClause annot -> ExceptClause annot -> ExceptClause annot Source #

min :: ExceptClause annot -> ExceptClause annot -> ExceptClause annot Source #

Show annot => Show (ExceptClause annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Pretty (ExceptClause a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: ExceptClause a -> Doc Source #

data RaiseExpr annot Source #

The argument for a raise statement.

Constructors

RaiseV3 (Maybe (Expr annot, Maybe (Expr annot)))

Optional expression to evaluate, and optional 'from' clause. Version 3 only.

RaiseV2 (Maybe (Expr annot, Maybe (Expr annot, Maybe (Expr annot))))

Version 2 only.

Instances
Functor RaiseExpr Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> RaiseExpr a -> RaiseExpr b Source #

(<$) :: a -> RaiseExpr b -> RaiseExpr a Source #

Eq annot => Eq (RaiseExpr annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: RaiseExpr annot -> RaiseExpr annot -> Bool Source #

(/=) :: RaiseExpr annot -> RaiseExpr annot -> Bool Source #

Data annot => Data (RaiseExpr annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RaiseExpr annot -> c (RaiseExpr annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RaiseExpr annot) Source #

toConstr :: RaiseExpr annot -> Constr Source #

dataTypeOf :: RaiseExpr annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RaiseExpr annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RaiseExpr annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> RaiseExpr annot -> RaiseExpr annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RaiseExpr annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RaiseExpr annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RaiseExpr annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RaiseExpr annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RaiseExpr annot -> m (RaiseExpr annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RaiseExpr annot -> m (RaiseExpr annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RaiseExpr annot -> m (RaiseExpr annot) Source #

Ord annot => Ord (RaiseExpr annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: RaiseExpr annot -> RaiseExpr annot -> Ordering Source #

(<) :: RaiseExpr annot -> RaiseExpr annot -> Bool Source #

(<=) :: RaiseExpr annot -> RaiseExpr annot -> Bool Source #

(>) :: RaiseExpr annot -> RaiseExpr annot -> Bool Source #

(>=) :: RaiseExpr annot -> RaiseExpr annot -> Bool Source #

max :: RaiseExpr annot -> RaiseExpr annot -> RaiseExpr annot Source #

min :: RaiseExpr annot -> RaiseExpr annot -> RaiseExpr annot Source #

Show annot => Show (RaiseExpr annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> RaiseExpr annot -> ShowS Source #

show :: RaiseExpr annot -> String Source #

showList :: [RaiseExpr annot] -> ShowS Source #

Pretty (RaiseExpr a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: RaiseExpr a -> Doc Source #

Comprehensions

data Comprehension annot Source #

Comprehension. In version 3.x this can be used for lists, sets, dictionaries and generators. data Comprehension e annot

Instances
Functor Comprehension Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> Comprehension a -> Comprehension b Source #

(<$) :: a -> Comprehension b -> Comprehension a Source #

Span ComprehensionSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated Comprehension Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: Comprehension annot -> annot Source #

Eq annot => Eq (Comprehension annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: Comprehension annot -> Comprehension annot -> Bool Source #

(/=) :: Comprehension annot -> Comprehension annot -> Bool Source #

Data annot => Data (Comprehension annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Comprehension annot -> c (Comprehension annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Comprehension annot) Source #

toConstr :: Comprehension annot -> Constr Source #

dataTypeOf :: Comprehension annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Comprehension annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Comprehension annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> Comprehension annot -> Comprehension annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Comprehension annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Comprehension annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Comprehension annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Comprehension annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Comprehension annot -> m (Comprehension annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Comprehension annot -> m (Comprehension annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Comprehension annot -> m (Comprehension annot) Source #

Ord annot => Ord (Comprehension annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Show annot => Show (Comprehension annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Pretty (Comprehension a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

data ComprehensionExpr annot Source #

Instances
Functor ComprehensionExpr Source # 
Instance details

Defined in Language.Python.Common.AST

Span ComprehensionExprSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Eq annot => Eq (ComprehensionExpr annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Data annot => Data (ComprehensionExpr annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ComprehensionExpr annot -> c (ComprehensionExpr annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ComprehensionExpr annot) Source #

toConstr :: ComprehensionExpr annot -> Constr Source #

dataTypeOf :: ComprehensionExpr annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ComprehensionExpr annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ComprehensionExpr annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> ComprehensionExpr annot -> ComprehensionExpr annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ComprehensionExpr annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ComprehensionExpr annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ComprehensionExpr annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ComprehensionExpr annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ComprehensionExpr annot -> m (ComprehensionExpr annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ComprehensionExpr annot -> m (ComprehensionExpr annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ComprehensionExpr annot -> m (ComprehensionExpr annot) Source #

Ord annot => Ord (ComprehensionExpr annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Show annot => Show (ComprehensionExpr annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Pretty (ComprehensionExpr a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

data CompFor annot Source #

Comprehension 'for' component.

Constructors

CompFor 

Fields

Instances
Functor CompFor Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> CompFor a -> CompFor b Source #

(<$) :: a -> CompFor b -> CompFor a Source #

Span CompForSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated CompFor Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: CompFor annot -> annot Source #

Eq annot => Eq (CompFor annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: CompFor annot -> CompFor annot -> Bool Source #

(/=) :: CompFor annot -> CompFor annot -> Bool Source #

Data annot => Data (CompFor annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompFor annot -> c (CompFor annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CompFor annot) Source #

toConstr :: CompFor annot -> Constr Source #

dataTypeOf :: CompFor annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (CompFor annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CompFor annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> CompFor annot -> CompFor annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompFor annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompFor annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CompFor annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompFor annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompFor annot -> m (CompFor annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompFor annot -> m (CompFor annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompFor annot -> m (CompFor annot) Source #

Ord annot => Ord (CompFor annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: CompFor annot -> CompFor annot -> Ordering Source #

(<) :: CompFor annot -> CompFor annot -> Bool Source #

(<=) :: CompFor annot -> CompFor annot -> Bool Source #

(>) :: CompFor annot -> CompFor annot -> Bool Source #

(>=) :: CompFor annot -> CompFor annot -> Bool Source #

max :: CompFor annot -> CompFor annot -> CompFor annot Source #

min :: CompFor annot -> CompFor annot -> CompFor annot Source #

Show annot => Show (CompFor annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> CompFor annot -> ShowS Source #

show :: CompFor annot -> String Source #

showList :: [CompFor annot] -> ShowS Source #

Pretty (CompFor a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: CompFor a -> Doc Source #

data CompIf annot Source #

Comprehension guard.

Constructors

CompIf 

Fields

Instances
Functor CompIf Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> CompIf a -> CompIf b Source #

(<$) :: a -> CompIf b -> CompIf a Source #

Span CompIfSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated CompIf Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: CompIf annot -> annot Source #

Eq annot => Eq (CompIf annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: CompIf annot -> CompIf annot -> Bool Source #

(/=) :: CompIf annot -> CompIf annot -> Bool Source #

Data annot => Data (CompIf annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompIf annot -> c (CompIf annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CompIf annot) Source #

toConstr :: CompIf annot -> Constr Source #

dataTypeOf :: CompIf annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (CompIf annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CompIf annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> CompIf annot -> CompIf annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompIf annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompIf annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CompIf annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompIf annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompIf annot -> m (CompIf annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompIf annot -> m (CompIf annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompIf annot -> m (CompIf annot) Source #

Ord annot => Ord (CompIf annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: CompIf annot -> CompIf annot -> Ordering Source #

(<) :: CompIf annot -> CompIf annot -> Bool Source #

(<=) :: CompIf annot -> CompIf annot -> Bool Source #

(>) :: CompIf annot -> CompIf annot -> Bool Source #

(>=) :: CompIf annot -> CompIf annot -> Bool Source #

max :: CompIf annot -> CompIf annot -> CompIf annot Source #

min :: CompIf annot -> CompIf annot -> CompIf annot Source #

Show annot => Show (CompIf annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> CompIf annot -> ShowS Source #

show :: CompIf annot -> String Source #

showList :: [CompIf annot] -> ShowS Source #

Pretty (CompIf a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: CompIf a -> Doc Source #

data CompIter annot Source #

Comprehension iterator (either a 'for' or an 'if').

Constructors

IterFor 

Fields

IterIf 

Fields

Instances
Functor CompIter Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

fmap :: (a -> b) -> CompIter a -> CompIter b Source #

(<$) :: a -> CompIter b -> CompIter a Source #

Span CompIterSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Annotated CompIter Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

annot :: CompIter annot -> annot Source #

Eq annot => Eq (CompIter annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

(==) :: CompIter annot -> CompIter annot -> Bool Source #

(/=) :: CompIter annot -> CompIter annot -> Bool Source #

Data annot => Data (CompIter annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompIter annot -> c (CompIter annot) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CompIter annot) Source #

toConstr :: CompIter annot -> Constr Source #

dataTypeOf :: CompIter annot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (CompIter annot)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CompIter annot)) Source #

gmapT :: (forall b. Data b => b -> b) -> CompIter annot -> CompIter annot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompIter annot -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompIter annot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CompIter annot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompIter annot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompIter annot -> m (CompIter annot) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompIter annot -> m (CompIter annot) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompIter annot -> m (CompIter annot) Source #

Ord annot => Ord (CompIter annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

compare :: CompIter annot -> CompIter annot -> Ordering Source #

(<) :: CompIter annot -> CompIter annot -> Bool Source #

(<=) :: CompIter annot -> CompIter annot -> Bool Source #

(>) :: CompIter annot -> CompIter annot -> Bool Source #

(>=) :: CompIter annot -> CompIter annot -> Bool Source #

max :: CompIter annot -> CompIter annot -> CompIter annot Source #

min :: CompIter annot -> CompIter annot -> CompIter annot Source #

Show annot => Show (CompIter annot) Source # 
Instance details

Defined in Language.Python.Common.AST

Methods

showsPrec :: Int -> CompIter annot -> ShowS Source #

show :: CompIter annot -> String Source #

showList :: [CompIter annot] -> ShowS Source #

Pretty (CompIter a) Source # 
Instance details

Defined in Language.Python.Common.PrettyAST

Methods

pretty :: CompIter a -> Doc Source #