language-python-0.5.2: 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

Modules

newtype Module annot Source

Constructors

Module [Statement annot]

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

Instances

Functor Module Source 
Eq annot => Eq (Module annot) Source 
Data annot => Data (Module annot) Source 
Ord annot => Ord (Module annot) Source 
Show annot => Show (Module annot) Source 

Identifiers and dotted names

data Ident annot Source

Identifier.

Constructors

Ident 

Fields

ident_string :: !String
 
ident_annot :: annot
 

Instances

Functor Ident Source 
Span IdentSpan Source 
Annotated Ident Source 
Eq annot => Eq (Ident annot) Source 
Data annot => Data (Ident annot) Source 
Ord annot => Ord (Ident annot) Source 
Show annot => Show (Ident annot) 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

import_items :: [ImportItem annot]

Items to import.

stmt_annot :: annot
 
FromImport

From ... import statement.

Fields

from_module :: ImportRelative annot

Module to import from.

from_items :: FromItems annot

Items to import.

stmt_annot :: annot
 
While

While loop.

Fields

while_cond :: Expr annot

Loop condition.

while_body :: Suite annot

Loop body.

while_else :: Suite annot

Else clause.

stmt_annot :: annot
 
For

For loop.

Fields

for_targets :: [Expr annot]

Loop variables.

for_generator :: Expr annot

Loop generator.

for_body :: Suite annot

Loop body

for_else :: Suite annot

Else clause.

stmt_annot :: annot
 
Fun

Function definition.

Fields

fun_name :: Ident annot

Function name.

fun_args :: [Parameter annot]

Function parameter list.

fun_result_annotation :: Maybe (Expr annot)

Optional result annotation.

fun_body :: Suite annot

Function body.

stmt_annot :: annot
 
Class

Class definition.

Fields

class_name :: Ident annot

Class name.

class_args :: [Argument annot]

Class argument list. In version 2.x this is only ArgExprs.

class_body :: Suite annot

Class body.

stmt_annot :: annot
 
Conditional

Conditional statement (if-elif-else).

Fields

cond_guards :: [(Expr annot, Suite annot)]

Sequence of if-elif conditional clauses.

cond_else :: Suite annot

Possibly empty unconditional else clause.

stmt_annot :: annot
 
Assign

Assignment statement.

Fields

assign_to :: [Expr annot]

Entity to assign to.

assign_expr :: Expr annot

Expression to evaluate.

stmt_annot :: annot
 
AugmentedAssign

Augmented assignment statement.

Fields

aug_assign_to :: Expr annot

Entity to assign to.

aug_assign_op :: AssignOp annot

Assignment operator (for example '+=').

aug_assign_expr :: Expr annot

Expression to evaluate.

stmt_annot :: annot
 
Decorated

Decorated definition of a function or class.

Fields

decorated_decorators :: [Decorator annot]

Decorators.

decorated_def :: Statement annot

Function or class definition to be decorated.

stmt_annot :: annot
 
Return

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

Fields

return_expr :: Maybe (Expr annot)

Optional expression to evaluate and return to caller.

stmt_annot :: annot
 
Try

Try statement (exception handling).

Fields

try_body :: Suite annot

Try clause.

try_excepts :: [Handler annot]

Exception handlers.

try_else :: Suite annot

Possibly empty else clause, executed if and when control flows off the end of the try clause.

try_finally :: Suite annot

Possibly empty finally clause.

stmt_annot :: annot
 
Raise

Raise statement (exception throwing).

Fields

raise_expr :: RaiseExpr annot
 
stmt_annot :: annot
 
With

With statement (context management).

Fields

with_context :: [(Expr annot, Maybe (Expr annot))]

Context expression(s) (yields a context manager).

with_body :: Suite annot

Suite to be managed.

stmt_annot :: annot
 
Pass

Pass statement (null operation).

Fields

stmt_annot :: annot
 
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

stmt_annot :: annot
 
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

stmt_annot :: annot
 
Delete

Del statement (delete).

Fields

del_exprs :: [Expr annot]

Items to delete.

stmt_annot :: annot
 
StmtExpr

Expression statement.

Fields

stmt_expr :: Expr annot
 
stmt_annot :: annot
 
Global

Global declaration.

Fields

global_vars :: [Ident annot]

Variables declared global in the current block.

stmt_annot :: annot
 
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

assert_exprs :: [Expr annot]

Expressions being asserted.

stmt_annot :: annot
 
Print

Print statement. Version 2 only.

Fields

print_chevron :: Bool

Optional chevron (>>)

print_exprs :: [Expr annot]

Arguments to print

print_trailing_comma :: Bool

Does it end in a comma?

stmt_annot :: annot
 
Exec

Exec statement. Version 2 only.

Fields

exec_expr :: Expr annot

Expression to exec.

exec_globals_locals :: Maybe (Expr annot, Maybe (Expr annot))

Global and local environments to evaluate the expression within.

stmt_annot :: annot
 

Instances

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

param_name :: Ident annot

Parameter name.

param_py_annotation :: Maybe (Expr annot)

Optional annotation.

param_default :: Maybe (Expr annot)

Optional default value.

param_annot :: annot
 
VarArgsPos

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

Fields

param_name :: Ident annot

Parameter name.

param_py_annotation :: Maybe (Expr annot)

Optional annotation.

param_annot :: annot
 
VarArgsKeyword

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

Fields

param_name :: Ident annot

Parameter name.

param_py_annotation :: Maybe (Expr annot)

Optional annotation.

param_annot :: annot
 
EndPositional

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

Fields

param_annot :: annot
 
UnPackTuple

Tuple unpack. Version 2 only.

Fields

param_unpack_tuple :: ParamTuple annot

The tuple to unpack.

param_default :: Maybe (Expr annot)

Optional default value.

param_annot :: annot
 

Instances

data ParamTuple annot Source

Tuple unpack parameter. Version 2 only.

Constructors

ParamTupleName

A variable name.

Fields

param_tuple_name :: Ident annot
 
param_tuple_annot :: annot
 
ParamTuple

A (possibly nested) tuple parameter.

Fields

param_tuple :: [ParamTuple annot]
 
param_tuple_annot :: annot
 

Instances

data Decorator annot Source

Decorator.

Constructors

Decorator 

Fields

decorator_name :: DottedName annot

Decorator name.

decorator_args :: [Argument annot]

Decorator arguments.

decorator_annot :: annot
 

Instances

data AssignOp annot Source

Augmented assignment operators.

Constructors

PlusAssign

'+='

Fields

assignOp_annot :: annot
 
MinusAssign

'-='

Fields

assignOp_annot :: annot
 
MultAssign

'*='

Fields

assignOp_annot :: annot
 
DivAssign

'/='

Fields

assignOp_annot :: annot
 
ModAssign

'%='

Fields

assignOp_annot :: annot
 
PowAssign

'*='

Fields

assignOp_annot :: annot
 
BinAndAssign

'&='

Fields

assignOp_annot :: annot
 
BinOrAssign

'|='

Fields

assignOp_annot :: annot
 
BinXorAssign

'^='

Fields

assignOp_annot :: annot
 
LeftShiftAssign

'<<='

Fields

assignOp_annot :: annot
 
RightShiftAssign

'>>='

Fields

assignOp_annot :: annot
 
FloorDivAssign

'//='

Fields

assignOp_annot :: annot
 

Instances

Functor AssignOp Source 
Span AssignOpSpan Source 
Annotated AssignOp Source 
Eq annot => Eq (AssignOp annot) Source 
Data annot => Data (AssignOp annot) Source 
Ord annot => Ord (AssignOp annot) Source 
Show annot => Show (AssignOp annot) Source 

Expressions, operators, arguments and slices

data Expr annot Source

Constructors

Var

Variable.

Fields

var_ident :: Ident annot
 
expr_annot :: annot
 
Int

Literal integer.

LongInt

Long literal integer. Version 2 only.

Float

Literal floating point number.

Imaginary

Literal imaginary number.

Bool

Literal boolean.

Fields

bool_value :: Bool
 
expr_annot :: annot
 
None

Literal 'None' value.

Fields

expr_annot :: annot
 
Ellipsis

Ellipsis '...'.

Fields

expr_annot :: annot
 
ByteStrings

Literal byte string.

Fields

byte_string_strings :: [String]
 
expr_annot :: annot
 
Strings

Literal strings (to be concatentated together).

Fields

strings_strings :: [String]
 
expr_annot :: annot
 
UnicodeStrings

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

Call

Function call.

Fields

call_fun :: Expr annot

Expression yielding a callable object (such as a function).

call_args :: [Argument annot]

Call arguments.

expr_annot :: annot
 
Subscript

Subscription, for example 'x [y]'.

Fields

subscriptee :: Expr annot
 
subscript_expr :: Expr annot
 
expr_annot :: annot
 
SlicedExpr

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

Fields

slicee :: Expr annot
 
slices :: [Slice annot]
 
expr_annot :: annot
 
CondExpr

Conditional expresison.

Fields

ce_true_branch :: Expr annot

Expression to evaluate if condition is True.

ce_condition :: Expr annot

Boolean condition.

ce_false_branch :: Expr annot

Expression to evaluate if condition is False.

expr_annot :: annot
 
BinaryOp

Binary operator application.

Fields

operator :: Op annot
 
left_op_arg :: Expr annot
 
right_op_arg :: Expr annot
 
expr_annot :: annot
 
UnaryOp

Unary operator application.

Fields

operator :: Op annot
 
op_arg :: Expr annot
 
expr_annot :: annot
 
Dot 

Fields

dot_expr :: Expr annot
 
dot_attribute :: Ident annot
 
expr_annot :: annot
 
Lambda

Anonymous function definition (lambda).

Fields

lambda_args :: [Parameter annot]
 
lambda_body :: Expr annot
 
expr_annot :: annot
 
Tuple

Tuple. Can be empty.

Fields

tuple_exprs :: [Expr annot]
 
expr_annot :: annot
 
Yield

Generator yield.

Fields

yield_arg :: Maybe (YieldArg annot)

Optional Yield argument.

expr_annot :: annot
 
Generator

Generator.

Fields

gen_comprehension :: Comprehension annot
 
expr_annot :: annot
 
ListComp

List comprehension.

Fields

list_comprehension :: Comprehension annot
 
expr_annot :: annot
 
List

List.

Fields

list_exprs :: [Expr annot]
 
expr_annot :: annot
 
Dictionary

Dictionary.

Fields

dict_mappings :: [DictMappingPair annot]
 
expr_annot :: annot
 
DictComp

Dictionary comprehension. Version 3 only.

Fields

dict_comprehension :: Comprehension annot
 
expr_annot :: annot
 
Set

Set.

Fields

set_exprs :: [Expr annot]
 
expr_annot :: annot
 
SetComp

Set comprehension. Version 3 only.

Fields

set_comprehension :: Comprehension annot
 
expr_annot :: annot
 
Starred

Starred expression. Version 3 only.

Fields

starred_expr :: Expr annot
 
expr_annot :: annot
 
Paren

Parenthesised expression.

Fields

paren_expr :: Expr annot
 
expr_annot :: annot
 
StringConversion

String conversion (backquoted expression). Version 2 only.

Fields

backquoted_expr :: Expr annot
 
expr_anot :: annot
 

Instances

Functor Expr Source 
Span ExprSpan Source 
Annotated Expr Source 
Eq annot => Eq (Expr annot) Source 
Data annot => Data (Expr annot) Source 
Ord annot => Ord (Expr annot) Source 
Show annot => Show (Expr annot) Source 

data Op annot Source

Operators.

Constructors

And

'and'

Fields

op_annot :: annot
 
Or

'or'

Fields

op_annot :: annot
 
Not

'not'

Fields

op_annot :: annot
 
Exponent

'**'

Fields

op_annot :: annot
 
LessThan

'<'

Fields

op_annot :: annot
 
GreaterThan

'>'

Fields

op_annot :: annot
 
Equality

'=='

Fields

op_annot :: annot
 
GreaterThanEquals

'>='

Fields

op_annot :: annot
 
LessThanEquals

'<='

Fields

op_annot :: annot
 
NotEquals

'!='

Fields

op_annot :: annot
 
NotEqualsV2

'<>'. Version 2 only.

Fields

op_annot :: annot
 
In

'in'

Fields

op_annot :: annot
 
Is

'is'

Fields

op_annot :: annot
 
IsNot

'is not'

Fields

op_annot :: annot
 
NotIn

'not in'

Fields

op_annot :: annot
 
BinaryOr

'|'

Fields

op_annot :: annot
 
Xor

'^'

Fields

op_annot :: annot
 
BinaryAnd

'&'

Fields

op_annot :: annot
 
ShiftLeft

'<<'

Fields

op_annot :: annot
 
ShiftRight

'>>'

Fields

op_annot :: annot
 
Multiply

'*'

Fields

op_annot :: annot
 
Plus

'+'

Fields

op_annot :: annot
 
Minus

'-'

Fields

op_annot :: annot
 
Divide

'/'

Fields

op_annot :: annot
 
FloorDivide

'//'

Fields

op_annot :: annot
 
Invert

'~' (bitwise inversion of its integer argument)

Fields

op_annot :: annot
 
Modulo

'%'

Fields

op_annot :: annot
 

Instances

Functor Op Source 
Span OpSpan Source 
Annotated Op Source 
Eq annot => Eq (Op annot) Source 
Data annot => Data (Op annot) Source 
Ord annot => Ord (Op annot) Source 
Show annot => Show (Op annot) Source 

data Argument annot Source

Arguments to function calls, class declarations and decorators.

Constructors

ArgExpr

Ordinary argument expression.

Fields

arg_expr :: Expr annot

Argument expression.

arg_annot :: annot
 
ArgVarArgsPos

Excess positional argument.

Fields

arg_expr :: Expr annot

Argument expression.

arg_annot :: annot
 
ArgVarArgsKeyword

Excess keyword argument.

Fields

arg_expr :: Expr annot

Argument expression.

arg_annot :: annot
 
ArgKeyword

Keyword argument.

Fields

arg_keyword :: Ident annot

Keyword name.

arg_expr :: Expr annot

Argument expression.

arg_annot :: annot
 

Instances

Functor Argument Source 
Span ArgumentSpan Source 
Annotated Argument Source 
Eq annot => Eq (Argument annot) Source 
Data annot => Data (Argument annot) Source 
Ord annot => Ord (Argument annot) Source 
Show annot => Show (Argument annot) Source 

data Slice annot Source

Slice compenent.

Constructors

SliceProper 

Fields

slice_lower :: Maybe (Expr annot)
 
slice_upper :: Maybe (Expr annot)
 
slice_stride :: Maybe (Maybe (Expr annot))
 
slice_annot :: annot
 
SliceExpr 

Fields

slice_expr :: Expr annot
 
slice_annot :: annot
 
SliceEllipsis 

Fields

slice_annot :: annot
 

Instances

Functor Slice Source 
Span SliceSpan Source 
Annotated Slice Source 
Eq annot => Eq (Slice annot) Source 
Data annot => Data (Slice annot) Source 
Ord annot => Ord (Slice annot) Source 
Show annot => Show (Slice annot) Source 

data DictMappingPair annot Source

Constructors

DictMappingPair (Expr annot) (Expr annot) 

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 
Span YieldArgSpan Source 
Eq annot => Eq (YieldArg annot) Source 
Data annot => Data (YieldArg annot) Source 
Ord annot => Ord (YieldArg annot) Source 
Show annot => Show (YieldArg annot) Source 

Imports

data ImportItem annot Source

Constructors

ImportItem 

Fields

import_item_name :: DottedName annot

The 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
 

Instances

data FromItem annot Source

Constructors

FromItem 

Fields

from_item_name :: Ident annot

The 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
 

Instances

Functor FromItem Source 
Span FromItemSpan Source 
Annotated FromItem Source 
Eq annot => Eq (FromItem annot) Source 
Data annot => Data (FromItem annot) Source 
Ord annot => Ord (FromItem annot) Source 
Show annot => Show (FromItem annot) Source 

data FromItems annot Source

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

Constructors

ImportEverything

Import everything exported from the module.

Fields

from_items_annot :: annot
 
FromItems

Import a specific list of items from the module.

Fields

from_items_items :: [FromItem annot]
 
from_items_annot :: annot
 

Instances

data ImportRelative annot Source

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

Exceptions

data Handler annot Source

Exception handler.

Constructors

Handler 

Fields

handler_clause :: ExceptClause annot
 
handler_suite :: Suite annot
 
handler_annot :: annot
 

Instances

Functor Handler Source 
Span HandlerSpan Source 
Annotated Handler Source 
Eq annot => Eq (Handler annot) Source 
Data annot => Data (Handler annot) Source 
Ord annot => Ord (Handler annot) Source 
Show annot => Show (Handler annot) Source 

data ExceptClause annot Source

Exception clause.

Constructors

ExceptClause 

Fields

except_clause :: Maybe (Expr annot, Maybe (Expr annot))
 
except_clause_annot :: annot
 

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 
Eq annot => Eq (RaiseExpr annot) Source 
Data annot => Data (RaiseExpr annot) Source 
Ord annot => Ord (RaiseExpr annot) Source 
Show annot => Show (RaiseExpr annot) 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

data CompFor annot Source

Comprehension 'for' component.

Constructors

CompFor 

Fields

comp_for_exprs :: [Expr annot]
 
comp_in_expr :: Expr annot
 
comp_for_iter :: Maybe (CompIter annot)
 
comp_for_annot :: annot
 

Instances

Functor CompFor Source 
Span CompForSpan Source 
Annotated CompFor Source 
Eq annot => Eq (CompFor annot) Source 
Data annot => Data (CompFor annot) Source 
Ord annot => Ord (CompFor annot) Source 
Show annot => Show (CompFor annot) Source 

data CompIf annot Source

Comprehension guard.

Constructors

CompIf 

Fields

comp_if :: Expr annot
 
comp_if_iter :: Maybe (CompIter annot)
 
comp_if_annot :: annot
 

Instances

Functor CompIf Source 
Span CompIfSpan Source 
Annotated CompIf Source 
Eq annot => Eq (CompIf annot) Source 
Data annot => Data (CompIf annot) Source 
Ord annot => Ord (CompIf annot) Source 
Show annot => Show (CompIf annot) Source 

data CompIter annot Source

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

Constructors

IterFor 

Fields

comp_iter_for :: CompFor annot
 
comp_iter_annot :: annot
 
IterIf 

Fields

comp_iter_if :: CompIf annot
 
comp_iter_annot :: annot
 

Instances

Functor CompIter Source 
Span CompIterSpan Source 
Annotated CompIter Source 
Eq annot => Eq (CompIter annot) Source 
Data annot => Data (CompIter annot) Source 
Ord annot => Ord (CompIter annot) Source 
Show annot => Show (CompIter annot) Source