language-python-0.2: Parsing and pretty printing of Python code.Source codeContentsIndex
Language.Python.Common.AST
Portabilityghc
Stabilityexperimental
Maintainerbjpop@csse.unimelb.edu.au
Contents
Annotation projection
Modules
Identifiers and dotted names
Statements, suites, parameters, decorators and assignment operators
Expressions, operators, arguments and slices
Imports
Exceptions
Comprehensions
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
class Annotated t where
annot :: t annot -> annot
newtype Module annot = Module [Statement annot]
type ModuleSpan = Module SrcSpan
data Ident annot = Ident {
ident_string :: !String
ident_annot :: annot
}
type IdentSpan = Ident SrcSpan
type DottedName annot = [Ident annot]
type DottedNameSpan = DottedName SrcSpan
data Statement annot
= Import {
import_items :: [ImportItem annot]
stmt_annot :: annot
}
| FromImport {
from_module :: ImportRelative annot
from_items :: FromItems annot
stmt_annot :: annot
}
| While {
while_cond :: Expr annot
while_body :: Suite annot
while_else :: Suite annot
stmt_annot :: annot
}
| For {
for_targets :: [Expr annot]
for_generator :: Expr annot
for_body :: Suite annot
for_else :: Suite annot
stmt_annot :: annot
}
| Fun {
fun_name :: Ident annot
fun_args :: [Parameter annot]
fun_result_annotation :: Maybe (Expr annot)
fun_body :: Suite annot
stmt_annot :: annot
}
| Class {
class_name :: Ident annot
class_args :: [Argument annot]
class_body :: Suite annot
stmt_annot :: annot
}
| Conditional {
cond_guards :: [(Expr annot, Suite annot)]
cond_else :: Suite annot
stmt_annot :: annot
}
| Assign {
assign_to :: [Expr annot]
assign_expr :: Expr annot
stmt_annot :: annot
}
| AugmentedAssign {
aug_assign_to :: Expr annot
aug_assign_op :: AssignOp annot
aug_assign_expr :: Expr annot
stmt_annot :: annot
}
| Decorated {
decorated_decorators :: [Decorator annot]
decorated_def :: Statement annot
stmt_annot :: annot
}
| Return {
return_expr :: Maybe (Expr annot)
stmt_annot :: annot
}
| Try {
try_body :: Suite annot
try_excepts :: [Handler annot]
try_else :: Suite annot
try_finally :: Suite annot
stmt_annot :: annot
}
| Raise {
raise_expr :: RaiseExpr annot
stmt_annot :: annot
}
| With {
with_context :: [(Expr annot, Maybe (Expr annot))]
with_body :: Suite annot
stmt_annot :: annot
}
| Pass {
stmt_annot :: annot
}
| Break {
stmt_annot :: annot
}
| Continue {
stmt_annot :: annot
}
| Delete {
del_exprs :: [Expr annot]
stmt_annot :: annot
}
| StmtExpr {
stmt_expr :: Expr annot
stmt_annot :: annot
}
| Global {
global_vars :: [Ident annot]
stmt_annot :: annot
}
| NonLocal {
nonLocal_vars :: [Ident annot]
stmt_annot :: annot
}
| Assert {
assert_exprs :: [Expr annot]
stmt_annot :: annot
}
| Print {
print_chevron :: Bool
print_exprs :: [Expr annot]
print_trailing_comma :: Bool
stmt_annot :: annot
}
| Exec {
exec_expr :: Expr annot
exec_globals_locals :: Maybe (Expr annot, Maybe (Expr annot))
stmt_annot :: annot
}
type StatementSpan = Statement SrcSpan
type Suite annot = [Statement annot]
type SuiteSpan = Suite SrcSpan
data Parameter annot
= Param {
param_name :: Ident annot
param_py_annotation :: Maybe (Expr annot)
param_default :: Maybe (Expr annot)
param_annot :: annot
}
| VarArgsPos {
param_name :: Ident annot
param_py_annotation :: Maybe (Expr annot)
param_annot :: annot
}
| VarArgsKeyword {
param_name :: Ident annot
param_py_annotation :: Maybe (Expr annot)
param_annot :: annot
}
| EndPositional {
param_annot :: annot
}
| UnPackTuple {
param_unpack_tuple :: ParamTuple annot
param_default :: Maybe (Expr annot)
param_annot :: annot
}
type ParameterSpan = Parameter SrcSpan
data ParamTuple annot
= ParamTupleName {
param_tuple_name :: Ident annot
param_tuple_annot :: annot
}
| ParamTuple {
param_tuple :: [ParamTuple annot]
param_tuple_annot :: annot
}
type ParamTupleSpan = ParamTuple SrcSpan
data Decorator annot = Decorator {
decorator_name :: DottedName annot
decorator_args :: [Argument annot]
decorator_annot :: annot
}
type DecoratorSpan = Decorator SrcSpan
data AssignOp annot
= PlusAssign {
assignOp_annot :: annot
}
| MinusAssign {
assignOp_annot :: annot
}
| MultAssign {
assignOp_annot :: annot
}
| DivAssign {
assignOp_annot :: annot
}
| ModAssign {
assignOp_annot :: annot
}
| PowAssign {
assignOp_annot :: annot
}
| BinAndAssign {
assignOp_annot :: annot
}
| BinOrAssign {
assignOp_annot :: annot
}
| BinXorAssign {
assignOp_annot :: annot
}
| LeftShiftAssign {
assignOp_annot :: annot
}
| RightShiftAssign {
assignOp_annot :: annot
}
| FloorDivAssign {
assignOp_annot :: annot
}
type AssignOpSpan = AssignOp SrcSpan
data Expr annot
= Var {
var_ident :: Ident annot
expr_annot :: annot
}
| Int {
int_value :: Integer
expr_literal :: String
expr_annot :: annot
}
| LongInt {
int_value :: Integer
expr_literal :: String
expr_annot :: annot
}
| Float {
float_value :: Double
expr_literal :: String
expr_annot :: annot
}
| Imaginary {
imaginary_value :: Double
expr_literal :: String
expr_annot :: annot
}
| Bool {
bool_value :: Bool
expr_annot :: annot
}
| None {
expr_annot :: annot
}
| Ellipsis {
expr_annot :: annot
}
| ByteStrings {
byte_string_strings :: [String]
expr_annot :: annot
}
| Strings {
strings_strings :: [String]
expr_annot :: annot
}
| Call {
call_fun :: Expr annot
call_args :: [Argument annot]
expr_annot :: annot
}
| Subscript {
subscriptee :: Expr annot
subscript_exprs :: [Expr annot]
expr_annot :: annot
}
| SlicedExpr {
slicee :: Expr annot
slices :: [Slice annot]
expr_annot :: annot
}
| CondExpr {
ce_true_branch :: Expr annot
ce_condition :: Expr annot
ce_false_branch :: Expr annot
expr_annot :: annot
}
| BinaryOp {
operator :: Op annot
left_op_arg :: Expr annot
right_op_arg :: Expr annot
expr_annot :: annot
}
| UnaryOp {
operator :: Op annot
op_arg :: Expr annot
expr_annot :: annot
}
| Lambda {
lambda_args :: [Parameter annot]
lambda_body :: Expr annot
expr_annot :: annot
}
| Tuple {
tuple_exprs :: [Expr annot]
expr_annot :: annot
}
| Yield {
yield_expr :: Maybe (Expr annot)
expr_annot :: annot
}
| Generator {
gen_comprehension :: Comprehension (Expr annot) annot
expr_annot :: annot
}
| ListComp {
list_comprehension :: Comprehension (Expr annot) annot
expr_annot :: annot
}
| List {
list_exprs :: [Expr annot]
expr_annot :: annot
}
| Dictionary {
dict_mappings :: [(Expr annot, Expr annot)]
expr_annot :: annot
}
| DictComp {
dict_comprehension :: Comprehension (Expr annot, Expr annot) annot
expr_annot :: annot
}
| Set {
set_exprs :: [Expr annot]
expr_annot :: annot
}
| SetComp {
set_comprehension :: Comprehension (Expr annot) annot
expr_annot :: annot
}
| Starred {
starred_expr :: Expr annot
expr_annot :: annot
}
| Paren {
paren_expr :: Expr annot
expr_annot :: annot
}
| StringConversion {
backquoted_expr :: Expr annot
expr_anot :: annot
}
type ExprSpan = Expr SrcSpan
data Op annot
= And {
op_annot :: annot
}
| Or {
op_annot :: annot
}
| Not {
op_annot :: annot
}
| Exponent {
op_annot :: annot
}
| LessThan {
op_annot :: annot
}
| GreaterThan {
op_annot :: annot
}
| Equality {
op_annot :: annot
}
| GreaterThanEquals {
op_annot :: annot
}
| LessThanEquals {
op_annot :: annot
}
| NotEquals {
op_annot :: annot
}
| NotEqualsV2 {
op_annot :: annot
}
| In {
op_annot :: annot
}
| Is {
op_annot :: annot
}
| IsNot {
op_annot :: annot
}
| NotIn {
op_annot :: annot
}
| BinaryOr {
op_annot :: annot
}
| Xor {
op_annot :: annot
}
| BinaryAnd {
op_annot :: annot
}
| ShiftLeft {
op_annot :: annot
}
| ShiftRight {
op_annot :: annot
}
| Multiply {
op_annot :: annot
}
| Plus {
op_annot :: annot
}
| Minus {
op_annot :: annot
}
| Divide {
op_annot :: annot
}
| FloorDivide {
op_annot :: annot
}
| Invert {
op_annot :: annot
}
| Modulo {
op_annot :: annot
}
| Dot {
op_annot :: annot
}
type OpSpan = Op SrcSpan
data Argument annot
= ArgExpr {
arg_expr :: Expr annot
arg_annot :: annot
}
| ArgVarArgsPos {
arg_expr :: Expr annot
arg_annot :: annot
}
| ArgVarArgsKeyword {
arg_expr :: Expr annot
arg_annot :: annot
}
| ArgKeyword {
arg_keyword :: Ident annot
arg_expr :: Expr annot
arg_annot :: annot
}
type ArgumentSpan = Argument SrcSpan
data Slice annot
= SliceProper {
slice_lower :: Maybe (Expr annot)
slice_upper :: Maybe (Expr annot)
slice_stride :: Maybe (Maybe (Expr annot))
slice_annot :: annot
}
| SliceExpr {
slice_expr :: Expr annot
slice_annot :: annot
}
| SliceEllipsis {
slice_annot :: annot
}
type SliceSpan = Slice SrcSpan
data ImportItem annot = ImportItem {
import_item_name :: DottedName annot
import_as_name :: Maybe (Ident annot)
import_item_annot :: annot
}
type ImportItemSpan = ImportItem SrcSpan
data FromItem annot = FromItem {
from_item_name :: Ident annot
from_as_name :: Maybe (Ident annot)
from_item_annot :: annot
}
type FromItemSpan = FromItem SrcSpan
data FromItems annot
= ImportEverything {
from_items_annot :: annot
}
| FromItems {
from_items_items :: [FromItem annot]
from_items_annot :: annot
}
type FromItemsSpan = FromItems SrcSpan
data ImportRelative annot = ImportRelative {
import_relative_dots :: Int
import_relative_module :: Maybe (DottedName annot)
import_relative_annot :: annot
}
type ImportRelativeSpan = ImportRelative SrcSpan
data Handler annot = Handler {
handler_clause :: ExceptClause annot
handler_suite :: Suite annot
handler_annot :: annot
}
type HandlerSpan = Handler SrcSpan
data ExceptClause annot = ExceptClause {
except_clause :: Maybe (Expr annot, Maybe (Expr annot))
except_clause_annot :: annot
}
type ExceptClauseSpan = ExceptClause SrcSpan
data RaiseExpr annot
= RaiseV3 (Maybe (Expr annot, Maybe (Expr annot)))
| RaiseV2 (Maybe (Expr annot, Maybe (Expr annot, Maybe (Expr annot))))
type RaiseExprSpan = RaiseExpr SrcSpan
data Comprehension e annot = Comprehension {
comprehension_expr :: e
comprehension_for :: CompFor annot
comprehension_annot :: annot
}
type ComprehensionSpan e = Comprehension e SrcSpan
data CompFor annot = CompFor {
comp_for_exprs :: [Expr annot]
comp_in_expr :: Expr annot
comp_for_iter :: Maybe (CompIter annot)
comp_for_annot :: annot
}
type CompForSpan = CompFor SrcSpan
data CompIf annot = CompIf {
comp_if :: Expr annot
comp_if_iter :: Maybe (CompIter annot)
comp_if_annot :: annot
}
type CompIfSpan = CompIf SrcSpan
data CompIter annot
= IterFor {
comp_iter_for :: CompFor annot
comp_iter_annot :: annot
}
| IterIf {
comp_iter_if :: CompIf annot
comp_iter_annot :: annot
}
type CompIterSpan = CompIter SrcSpan
Annotation projection
class Annotated t whereSource
Convenient access to annotations in annotated types.
Methods
annot :: t annot -> annotSource
Given an annotated type, project out its annotation value.
show/hide Instances
Modules
newtype Module annot Source

A module (Python source file).

Constructors
Module [Statement annot]A module is just a sequence of top-level statements.
show/hide Instances
Typeable1 Module
Eq annot => Eq (Module annot)
Data annot => Data (Module annot)
Ord annot => Ord (Module annot)
Show annot => Show (Module annot)
Pretty (Module a)
type ModuleSpan = Module SrcSpanSource
Identifiers and dotted names
data Ident annot Source
Identifier.
Constructors
Ident
ident_string :: !String
ident_annot :: annot
show/hide Instances
Typeable1 Ident
Span IdentSpan
Annotated Ident
Eq annot => Eq (Ident annot)
Data annot => Data (Ident annot)
Ord annot => Ord (Ident annot)
Show annot => Show (Ident annot)
Pretty (Ident a)
type IdentSpan = Ident SrcSpanSource
type DottedName annot = [Ident annot]Source
A compound name constructed with the dot operator.
type DottedNameSpan = DottedName SrcSpanSource
Statements, suites, parameters, decorators and assignment operators
data Statement annot Source

Statements.

Constructors
ImportImport statement.
import_items :: [ImportItem annot]Items to import.
stmt_annot :: annot
FromImportFrom ... import statement.
from_module :: ImportRelative annotModule to import from.
from_items :: FromItems annotItems to import.
stmt_annot :: annot
WhileWhile loop.
while_cond :: Expr annotLoop condition.
while_body :: Suite annotLoop body.
while_else :: Suite annotElse clause.
stmt_annot :: annot
ForFor loop.
for_targets :: [Expr annot]Loop variables.
for_generator :: Expr annotLoop generator.
for_body :: Suite annotLoop body
for_else :: Suite annotElse clause.
stmt_annot :: annot
FunFunction definition.
fun_name :: Ident annotFunction name.
fun_args :: [Parameter annot]Function parameter list.
fun_result_annotation :: Maybe (Expr annot)Optional result annotation.
fun_body :: Suite annotFunction body.
stmt_annot :: annot
ClassClass definition.
class_name :: Ident annotClass name.
class_args :: [Argument annot]Class argument list. In version 2.x this is only ArgExprs.
class_body :: Suite annotClass body.
stmt_annot :: annot
ConditionalConditional statement (if-elif-else).
cond_guards :: [(Expr annot, Suite annot)]Sequence of if-elif conditional clauses.
cond_else :: Suite annotPossibly empty unconditional else clause.
stmt_annot :: annot
AssignAssignment statement.
assign_to :: [Expr annot]Entity to assign to.
assign_expr :: Expr annotExpression to evaluate.
stmt_annot :: annot
AugmentedAssignAugmented assignment statement.
aug_assign_to :: Expr annotEntity to assign to.
aug_assign_op :: AssignOp annotAssignment operator (for example '+=').
aug_assign_expr :: Expr annotExpression to evaluate.
stmt_annot :: annot
DecoratedDecorated definition of a function or class.
decorated_decorators :: [Decorator annot]Decorators.
decorated_def :: Statement annotFunction or class definition to be decorated.
stmt_annot :: annot
ReturnReturn statement (may only occur syntactically nested in a function definition).
return_expr :: Maybe (Expr annot)Optional expression to evaluate and return to caller.
stmt_annot :: annot
TryTry statement (exception handling).
try_body :: Suite annotTry clause.
try_excepts :: [Handler annot]Exception handlers.
try_else :: Suite annotPossibly empty else clause, executed if and when control flows off the end of the try clause.
try_finally :: Suite annotPossibly empty finally clause.
stmt_annot :: annot
RaiseRaise statement (exception throwing).
raise_expr :: RaiseExpr annot
stmt_annot :: annot
WithWith statement (context management).
with_context :: [(Expr annot, Maybe (Expr annot))]Context expression(s) (yields a context manager).
with_body :: Suite annotSuite to be managed.
stmt_annot :: annot
PassPass statement (null operation).
stmt_annot :: annot
BreakBreak statement (may only occur syntactically nested in a for or while loop, but not nested in a function or class definition within that loop).
stmt_annot :: annot
ContinueContinue 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).
stmt_annot :: annot
DeleteDel statement (delete).
del_exprs :: [Expr annot]Items to delete.
stmt_annot :: annot
StmtExprExpression statement.
stmt_expr :: Expr annot
stmt_annot :: annot
GlobalGlobal declaration.
global_vars :: [Ident annot]Variables declared global in the current block.
stmt_annot :: annot
NonLocalNonlocal declaration. Version 3.x only.
nonLocal_vars :: [Ident annot]Variables declared nonlocal in the current block (their binding comes from bound the nearest enclosing scope).
stmt_annot :: annot
AssertAssertion.
assert_exprs :: [Expr annot]Expressions being asserted.
stmt_annot :: annot
PrintPrint statement. Version 2 only.
print_chevron :: BoolOptional chevron (>>)
print_exprs :: [Expr annot]Arguments to print
print_trailing_comma :: BoolDoes it end in a comma?
stmt_annot :: annot
ExecExec statement. Version 2 only.
exec_expr :: Expr annotExpression to exec.
exec_globals_locals :: Maybe (Expr annot, Maybe (Expr annot))Global and local environments to evaluate the expression within.
stmt_annot :: annot
show/hide Instances
type StatementSpan = Statement SrcSpanSource
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.

type SuiteSpan = Suite SrcSpanSource
data Parameter annot Source

Formal parameter of function definitions and lambda expressions.

Constructors
ParamOrdinary named parameter.
param_name :: Ident annotParameter name.
param_py_annotation :: Maybe (Expr annot)Optional annotation.
param_default :: Maybe (Expr annot)Optional default value.
param_annot :: annot
VarArgsPosExcess positional parameter (single asterisk before its name in the concrete syntax).
param_name :: Ident annotParameter name.
param_py_annotation :: Maybe (Expr annot)Optional annotation.
param_annot :: annot
VarArgsKeywordExcess keyword parameter (double asterisk before its name in the concrete syntax).
param_name :: Ident annotParameter name.
param_py_annotation :: Maybe (Expr annot)Optional annotation.
param_annot :: annot
EndPositionalMarker for the end of positional parameters (not a parameter itself).
param_annot :: annot
UnPackTupleTuple unpack. Version 2 only.
param_unpack_tuple :: ParamTuple annotThe tuple to unpack.
param_default :: Maybe (Expr annot)Optional default value.
param_annot :: annot
show/hide Instances
type ParameterSpan = Parameter SrcSpanSource
data ParamTuple annot Source
Tuple unpack parameter. Version 2 only.
Constructors
ParamTupleNameA variable name.
param_tuple_name :: Ident annot
param_tuple_annot :: annot
ParamTupleA (possibly nested) tuple parameter.
param_tuple :: [ParamTuple annot]
param_tuple_annot :: annot
show/hide Instances
type ParamTupleSpan = ParamTuple SrcSpanSource
data Decorator annot Source
Decorator.
Constructors
Decorator
decorator_name :: DottedName annotDecorator name.
decorator_args :: [Argument annot]Decorator arguments.
decorator_annot :: annot
show/hide Instances
type DecoratorSpan = Decorator SrcSpanSource
data AssignOp annot Source
Augmented assignment operators.
Constructors
PlusAssign'+='
assignOp_annot :: annot
MinusAssign'-='
assignOp_annot :: annot
MultAssign'*='
assignOp_annot :: annot
DivAssign'/='
assignOp_annot :: annot
ModAssign'%='
assignOp_annot :: annot
PowAssign'*='
assignOp_annot :: annot
BinAndAssign'&='
assignOp_annot :: annot
BinOrAssign'|='
assignOp_annot :: annot
BinXorAssign'^='
assignOp_annot :: annot
LeftShiftAssign'<<='
assignOp_annot :: annot
RightShiftAssign'>>='
assignOp_annot :: annot
FloorDivAssign'//='
assignOp_annot :: annot
show/hide Instances
Typeable1 AssignOp
Span AssignOpSpan
Annotated AssignOp
Eq annot => Eq (AssignOp annot)
Data annot => Data (AssignOp annot)
Ord annot => Ord (AssignOp annot)
Show annot => Show (AssignOp annot)
Pretty (AssignOp a)
type AssignOpSpan = AssignOp SrcSpanSource
Expressions, operators, arguments and slices
data Expr annot Source

Expressions.

Constructors
VarVariable.
var_ident :: Ident annot
expr_annot :: annot
IntLiteral integer.
int_value :: Integer
expr_literal :: String
expr_annot :: annot
LongIntLong literal integer. Version 2 only.
int_value :: Integer
expr_literal :: String
expr_annot :: annot
FloatLiteral floating point number.
float_value :: Double
expr_literal :: String
expr_annot :: annot
ImaginaryLiteral imaginary number.
imaginary_value :: Double
expr_literal :: String
expr_annot :: annot
BoolLiteral boolean.
bool_value :: Bool
expr_annot :: annot
NoneLiteral 'None' value.
expr_annot :: annot
EllipsisEllipsis '...'.
expr_annot :: annot
ByteStringsLiteral byte string.
byte_string_strings :: [String]
expr_annot :: annot
StringsLiteral strings (to be concatentated together).
strings_strings :: [String]
expr_annot :: annot
CallFunction call.
call_fun :: Expr annotExpression yielding a callable object (such as a function).
call_args :: [Argument annot]Call arguments.
expr_annot :: annot
SubscriptSubscription, for example 'x [y]'.
subscriptee :: Expr annot
subscript_exprs :: [Expr annot]
expr_annot :: annot
SlicedExprSlicing, for example 'w [x:y:z]'.
slicee :: Expr annot
slices :: [Slice annot]
expr_annot :: annot
CondExprConditional expresison.
ce_true_branch :: Expr annotExpression to evaluate if condition is True.
ce_condition :: Expr annotBoolean condition.
ce_false_branch :: Expr annotExpression to evaluate if condition is False.
expr_annot :: annot
BinaryOpBinary operator application.
operator :: Op annot
left_op_arg :: Expr annot
right_op_arg :: Expr annot
expr_annot :: annot
UnaryOpUnary operator application.
operator :: Op annot
op_arg :: Expr annot
expr_annot :: annot
LambdaAnonymous function definition (lambda).
lambda_args :: [Parameter annot]
lambda_body :: Expr annot
expr_annot :: annot
TupleTuple. Can be empty.
tuple_exprs :: [Expr annot]
expr_annot :: annot
YieldGenerator yield.
yield_expr :: Maybe (Expr annot)Optional expression to yield.
expr_annot :: annot
GeneratorGenerator.
gen_comprehension :: Comprehension (Expr annot) annot
expr_annot :: annot
ListCompList comprehension.
list_comprehension :: Comprehension (Expr annot) annot
expr_annot :: annot
ListList.
list_exprs :: [Expr annot]
expr_annot :: annot
DictionaryDictionary.
dict_mappings :: [(Expr annot, Expr annot)]
expr_annot :: annot
DictCompDictionary comprehension. Version 3 only.
dict_comprehension :: Comprehension (Expr annot, Expr annot) annot
expr_annot :: annot
SetSet.
set_exprs :: [Expr annot]
expr_annot :: annot
SetCompSet comprehension. Version 3 only.
set_comprehension :: Comprehension (Expr annot) annot
expr_annot :: annot
StarredStarred expression. Version 3 only.
starred_expr :: Expr annot
expr_annot :: annot
ParenParenthesised expression.
paren_expr :: Expr annot
expr_annot :: annot
StringConversionString conversion (backquoted expression). Version 2 only.
backquoted_expr :: Expr annot
expr_anot :: annot
show/hide Instances
Typeable1 Expr
Span ExprSpan
Annotated Expr
Eq annot => Eq (Expr annot)
Data annot => Data (Expr annot)
Ord annot => Ord (Expr annot)
Show annot => Show (Expr annot)
Pretty (Expr a)
type ExprSpan = Expr SrcSpanSource
data Op annot Source
Operators.
Constructors
And'and'
op_annot :: annot
Or'or'
op_annot :: annot
Not'not'
op_annot :: annot
Exponent'**'
op_annot :: annot
LessThan'<'
op_annot :: annot
GreaterThan'>'
op_annot :: annot
Equality'=='
op_annot :: annot
GreaterThanEquals'>='
op_annot :: annot
LessThanEquals'<='
op_annot :: annot
NotEquals'!='
op_annot :: annot
NotEqualsV2''. Version 2 only.
op_annot :: annot
In'in'
op_annot :: annot
Is'is'
op_annot :: annot
IsNot'is not'
op_annot :: annot
NotIn'not in'
op_annot :: annot
BinaryOr'|'
op_annot :: annot
Xor'^'
op_annot :: annot
BinaryAnd'&'
op_annot :: annot
ShiftLeft'<<'
op_annot :: annot
ShiftRight'>>'
op_annot :: annot
Multiply'*'
op_annot :: annot
Plus'+'
op_annot :: annot
Minus'-'
op_annot :: annot
Divide'/'
op_annot :: annot
FloorDivide'//'
op_annot :: annot
Invert'~' (bitwise inversion of its integer argument)
op_annot :: annot
Modulo'%'
op_annot :: annot
Dot'.'
op_annot :: annot
show/hide Instances
Typeable1 Op
Span OpSpan
Annotated Op
Eq annot => Eq (Op annot)
Data annot => Data (Op annot)
Ord annot => Ord (Op annot)
Show annot => Show (Op annot)
Pretty (Op a)
type OpSpan = Op SrcSpanSource
data Argument annot Source
Arguments to function calls, class declarations and decorators.
Constructors
ArgExprOrdinary argument expression.
arg_expr :: Expr annot
arg_annot :: annot
ArgVarArgsPosExcess positional argument.
arg_expr :: Expr annot
arg_annot :: annot
ArgVarArgsKeywordExcess keyword argument.
arg_expr :: Expr annot
arg_annot :: annot
ArgKeywordKeyword argument.
arg_keyword :: Ident annotKeyword name.
arg_expr :: Expr annotArgument expression.
arg_annot :: annot
show/hide Instances
Typeable1 Argument
Span ArgumentSpan
Annotated Argument
Eq annot => Eq (Argument annot)
Data annot => Data (Argument annot)
Ord annot => Ord (Argument annot)
Show annot => Show (Argument annot)
Pretty (Argument a)
type ArgumentSpan = Argument SrcSpanSource
data Slice annot Source
Slice compenent.
Constructors
SliceProper
slice_lower :: Maybe (Expr annot)
slice_upper :: Maybe (Expr annot)
slice_stride :: Maybe (Maybe (Expr annot))
slice_annot :: annot
SliceExpr
slice_expr :: Expr annot
slice_annot :: annot
SliceEllipsis
slice_annot :: annot
show/hide Instances
Typeable1 Slice
Span SliceSpan
Annotated Slice
Eq annot => Eq (Slice annot)
Data annot => Data (Slice annot)
Ord annot => Ord (Slice annot)
Show annot => Show (Slice annot)
Pretty (Slice a)
type SliceSpan = Slice SrcSpanSource
Imports
data ImportItem annot Source

An entity imported using the 'import' keyword.

Constructors
ImportItem
import_item_name :: DottedName annotThe name of module to import.
import_as_name :: Maybe (Ident annot)An optional name to refer to the entity (the 'as' name).
import_item_annot :: annot
show/hide Instances
type ImportItemSpan = ImportItem SrcSpanSource
data FromItem annot Source

An entity imported using the 'from ... import' construct.

Constructors
FromItem
from_item_name :: Ident annotThe name of the entity imported.
from_as_name :: Maybe (Ident annot)An optional name to refer to the entity (the 'as' name).
from_item_annot :: annot
show/hide Instances
Typeable1 FromItem
Span FromItemSpan
Annotated FromItem
Eq annot => Eq (FromItem annot)
Data annot => Data (FromItem annot)
Ord annot => Ord (FromItem annot)
Show annot => Show (FromItem annot)
Pretty (FromItem a)
type FromItemSpan = FromItem SrcSpanSource
data FromItems annot Source
Items imported using the 'from ... import' construct.
Constructors
ImportEverythingImport everything exported from the module.
from_items_annot :: annot
FromItemsImport a specific list of items from the module.
from_items_items :: [FromItem annot]
from_items_annot :: annot
show/hide Instances
type FromItemsSpan = FromItems SrcSpanSource
data ImportRelative annot Source
A reference to the module to import from using the 'from ... import' construct.
Constructors
ImportRelative
import_relative_dots :: Int
import_relative_module :: Maybe (DottedName annot)
import_relative_annot :: annot
show/hide Instances
type ImportRelativeSpan = ImportRelative SrcSpanSource
Exceptions
data Handler annot Source
Exception handler.
Constructors
Handler
handler_clause :: ExceptClause annot
handler_suite :: Suite annot
handler_annot :: annot
show/hide Instances
Typeable1 Handler
Span HandlerSpan
Annotated Handler
Eq annot => Eq (Handler annot)
Data annot => Data (Handler annot)
Ord annot => Ord (Handler annot)
Show annot => Show (Handler annot)
Pretty (Handler a)
type HandlerSpan = Handler SrcSpanSource
data ExceptClause annot Source
Exception clause.
Constructors
ExceptClause
except_clause :: Maybe (Expr annot, Maybe (Expr annot))
except_clause_annot :: annot
show/hide Instances
type ExceptClauseSpan = ExceptClause SrcSpanSource
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.
show/hide Instances
Typeable1 RaiseExpr
Eq annot => Eq (RaiseExpr annot)
Data annot => Data (RaiseExpr annot)
Ord annot => Ord (RaiseExpr annot)
Show annot => Show (RaiseExpr annot)
Pretty (RaiseExpr a)
type RaiseExprSpan = RaiseExpr SrcSpanSource
Comprehensions
data Comprehension e annot Source
Comprehension. In version 3.x this can be used for lists, sets, dictionaries and generators.
Constructors
Comprehension
comprehension_expr :: e
comprehension_for :: CompFor annot
comprehension_annot :: annot
show/hide Instances
Typeable2 Comprehension
Span (ComprehensionSpan e)
Annotated (Comprehension e)
(Eq e, Eq annot) => Eq (Comprehension e annot)
(Data e, Data annot) => Data (Comprehension e annot)
(Ord e, Ord annot) => Ord (Comprehension e annot)
(Show e, Show annot) => Show (Comprehension e annot)
Pretty t => Pretty (Comprehension t a)
type ComprehensionSpan e = Comprehension e SrcSpanSource
data CompFor annot Source
Comprehension 'for' component.
Constructors
CompFor
comp_for_exprs :: [Expr annot]
comp_in_expr :: Expr annot
comp_for_iter :: Maybe (CompIter annot)
comp_for_annot :: annot
show/hide Instances
Typeable1 CompFor
Span CompForSpan
Annotated CompFor
Eq annot => Eq (CompFor annot)
Data annot => Data (CompFor annot)
Ord annot => Ord (CompFor annot)
Show annot => Show (CompFor annot)
Pretty (CompFor a)
type CompForSpan = CompFor SrcSpanSource
data CompIf annot Source
Comprehension guard.
Constructors
CompIf
comp_if :: Expr annot
comp_if_iter :: Maybe (CompIter annot)
comp_if_annot :: annot
show/hide Instances
Typeable1 CompIf
Span CompIfSpan
Annotated CompIf
Eq annot => Eq (CompIf annot)
Data annot => Data (CompIf annot)
Ord annot => Ord (CompIf annot)
Show annot => Show (CompIf annot)
Pretty (CompIf a)
type CompIfSpan = CompIf SrcSpanSource
data CompIter annot Source
Comprehension iterator (either a 'for' or an 'if').
Constructors
IterFor
comp_iter_for :: CompFor annot
comp_iter_annot :: annot
IterIf
comp_iter_if :: CompIf annot
comp_iter_annot :: annot
show/hide Instances
Typeable1 CompIter
Span CompIterSpan
Annotated CompIter
Eq annot => Eq (CompIter annot)
Data annot => Data (CompIter annot)
Ord annot => Ord (CompIter annot)
Show annot => Show (CompIter annot)
Pretty (CompIter a)
type CompIterSpan = CompIter SrcSpanSource
Produced by Haddock version 2.4.2