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

Portabilityghc
Stabilityexperimental
Maintainerbjpop@csse.unimelb.edu.au

Language.Python.Version3.Syntax.AST

Contents

Description

Representation of the Python version 3 abstract syntax.

See:

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. XXX At some point we should provide smart constructors which ensure syntactic correctness of the AST.

Synopsis

Modules

newtype Module Source

Constructors

Module [Statement]

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

Instances

Identifiers and dotted names

newtype Ident Source

Identifier.

Constructors

Ident String 

type DottedName = [Ident]Source

A compound name constructed with the dot operator.

Statements, suites, parameters, decorators and assignment operators

data Statement Source

Constructors

Import

Import statement.

Fields

import_items :: [ImportItem]

Items to import.

FromImport

From ... import statement.

Fields

from_module :: ImportModule

Module to import from.

from_items :: FromItems

Items to import.

While

While loop. See http://docs.python.org/dev/3.0/reference/compound_stmts.html#the-while-statement.

Fields

while_cond :: Expr

Loop condition.

while_body :: Suite

Loop body.

while_else :: Suite

Else clause.

For

For loop. See http://docs.python.org/dev/3.0/reference/compound_stmts.html#the-for-statement.

Fields

for_targets :: [Expr]

Loop variables.

for_generator :: Expr

Loop generator.

for_body :: Suite

Loop body

for_else :: Suite

Else clause.

Fun

Function definition. See http://docs.python.org/dev/3.0/reference/compound_stmts.html#function-definitions.

Fields

fun_name :: Ident

Function name.

fun_args :: [Parameter]

Function parameter list.

fun_result_annotation :: Maybe Expr

Optional result annotation.

fun_body :: Suite

Function body.

Class

Class definition. See http://docs.python.org/dev/3.0/reference/compound_stmts.html#class-definitions.

Fields

class_name :: Ident

Class name.

class_args :: [Argument]

Class argument list.

class_body :: Suite

Class body.

Conditional

Conditional statement (if-elif-else). See http://docs.python.org/dev/3.0/reference/compound_stmts.html#the-if-statement.

Fields

cond_guards :: [(Expr, Suite)]

Sequence of if-elif conditional clauses.

cond_else :: Suite

Possibly empty unconditional else clause.

Assign

Assignment statement. See http://docs.python.org/dev/3.0/reference/simple_stmts.html#assignment-statements.

Fields

assign_to :: [Expr]

Entity to assign to. XXX perhaps this should not be a list.

assign_expr :: Expr

Expression to evaluate.

AugmentedAssign

Augmented assignment statement. See http://docs.python.org/dev/3.0/reference/simple_stmts.html#augmented-assignment-statements.

Fields

aug_assign_to :: Expr

Entity to assign to.

aug_assign_op :: AssignOp

Assignment operator (for example '+=').

aug_assign_expr :: Expr

Expression to evaluate.

Decorated

Decorated definition of a function or class.

Fields

decorated_decorators :: [Decorator]

Decorators.

decorated_def :: Statement

Function or class definition to be decorated.

Return

Return statement (may only occur syntactically nested in a function definition). See http://docs.python.org/dev/3.0/reference/simple_stmts.html#the-return-statement.

Fields

return_expr :: Maybe Expr

Optional expression to evaluate and return to caller.

Try

Try statement (exception handling). See http://docs.python.org/dev/3.0/reference/compound_stmts.html#the-try-statement.

Fields

try_body :: Suite

Try clause.

try_excepts :: [Handler]

Exception handlers.

try_else :: Suite

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

try_finally :: Suite

Possibly empty finally clause.

Raise

Raise statement (exception throwing). See: http://docs.python.org/dev/3.0/reference/simple_stmts.html#the-raise-statement

Fields

raise_expr :: Maybe (Expr, Maybe Expr)

Optional expression to evaluate, and optional 'from' clause.

With

With statement (context management). See http://docs.python.org/dev/3.0/reference/compound_stmts.html#the-with-statement. And also see: http://www.python.org/dev/peps/pep-0343/.

Fields

with_context :: Expr

Context expression (yields a context manager).

with_as :: Maybe Expr

Optional target.

with_body :: Suite

Suite to be managed.

Pass

Pass statement (null operation). See: http://docs.python.org/dev/3.0/reference/simple_stmts.html#the-pass-statement

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). See: http://docs.python.org/dev/3.0/reference/simple_stmts.html#the-break-statement.

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). See: http://docs.python.org/dev/3.0/reference/simple_stmts.html#the-continue-statement.

Delete

Del statement (delete). See: http://docs.python.org/dev/3.0/reference/simple_stmts.html#the-del-statement.

Fields

del_exprs :: [Expr]

Items to delete.

StmtExpr

Expression statement. See: http://docs.python.org/dev/3.0/reference/simple_stmts.html#expression-statements.

Fields

stmt_expr :: Expr
 
Global

Global declaration. See: http://docs.python.org/dev/3.0/reference/simple_stmts.html#the-global-statement.

Fields

global_vars :: [Ident]

Variables declared global in the current block.

NonLocal

Nonlocal declaration. See: http://docs.python.org/dev/3.0/reference/simple_stmts.html#the-nonlocal-statement.

Fields

nonLocal_vars :: [Ident]

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

Assert

Assertion. See: http://docs.python.org/dev/3.0/reference/simple_stmts.html#the-assert-statement.

Fields

assert_exprs :: [Expr]

Expressions being asserted.

type Suite = [Statement]Source

A block of statements. A suite is a group of statements controlled by a clause, for example, the body of a loop. See http://docs.python.org/dev/3.0/reference/compound_stmts.html.

data Parameter Source

Constructors

Param

Ordinary named parameter.

Fields

param_name :: Ident

Parameter name.

param_annotation :: Maybe Expr

Optional annotation.

param_default :: Maybe Expr

Optional default value.

VarArgsPos

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

Fields

param_name :: Ident

Parameter name.

param_annotation :: Maybe Expr

Optional annotation.

VarArgsKeyword

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

Fields

param_name :: Ident

Parameter name.

param_annotation :: Maybe Expr

Optional annotation.

EndPositional

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

data Decorator Source

Decorator.

Constructors

Decorator 

Fields

decorator_name :: DottedName

Decorator name.

decorator_args :: [Argument]

Decorator arguments.

data AssignOp Source

Augmented assignment operators.

Expressions, operators, arguments and slices

data Expr Source

Constructors

Var Ident

Variable.

Int Integer

Literal integer.

Float Double

Literal floating point number.

Imaginary

Literal imaginary number.

Bool Bool

Literal boolean.

None

Literal 'None' value.

Ellipsis

Ellipsis '...'.

ByteStrings [ByteString]

Literal byte string.

Strings [String]

Literal strings (to be concatentated together).

Call

Function call. See: http://docs.python.org/dev/3.0/reference/expressions.html#calls.

Fields

call_fun :: Expr

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

call_args :: [Argument]

Call arguments.

Subscript

Subscription, for example 'x [y]'. See: http://docs.python.org/dev/3.0/reference/expressions.html#id5.

SlicedExpr

Slicing, for example 'w [x:y:z]'. See: http://docs.python.org/dev/3.0/reference/expressions.html#id6.

Fields

slicee :: Expr
 
slices :: [Slice]
 
CondExpr

Conditional expresison. See: http://docs.python.org/dev/3.0/reference/expressions.html#boolean-operations.

Fields

ce_true_branch :: Expr

Expression to evaluate if condition is True.

ce_condition :: Expr

Boolean condition.

ce_false_branch :: Expr

Expression to evaluate if condition is False.

BinaryOp

Binary operator application.

UnaryOp

Unary operator application.

Fields

operator :: Op
 
op_arg :: Expr
 
Lambda

Anonymous function definition (lambda). See: http://docs.python.org/dev/3.0/reference/expressions.html#id15.

Tuple

N-ary tuple of arity greater than 0. The list should not be empty.

Fields

tuple_exprs :: [Expr]
 
Yield

Generator yield. See: http://docs.python.org/dev/3.0/reference/expressions.html#yield-expressions.

Fields

yield_expr :: Maybe Expr

Optional expression to yield.

Generator

Generator. See: http://docs.python.org/dev/3.0/reference/expressions.html#generator-expressions.

ListComp

List comprehension. See: http://docs.python.org/dev/3.0/reference/expressions.html#list-displays.

List

List. See: http://docs.python.org/dev/3.0/reference/expressions.html#list-displays.

Fields

list_exprs :: [Expr]
 
Dictionary

Dictionary. See: http://docs.python.org/dev/3.0/reference/expressions.html#dictionary-displays.

Fields

dict_mappings :: [(Expr, Expr)]
 
DictComp

Dictionary comprehension. See: http://docs.python.org/dev/3.0/reference/expressions.html#dictionary-displays.

Set

Set. See: http://docs.python.org/dev/3.0/reference/expressions.html#set-displays.

Fields

set_exprs :: [Expr]
 
SetComp

Set comprehension. http://docs.python.org/dev/3.0/reference/expressions.html#set-displays.

Starred

Starred expression.

Fields

starred_expr :: Expr
 

Instances

data Op Source

Operators.

Constructors

And

'and'

Or

'or'

Not

'not'

Exponent

'**'

LessThan

'<'

GreaterThan

'>'

Equality

'=='

GreaterThanEquals

'>='

LessThanEquals

'<='

NotEquals

'!='

In

'in'

Is

'is'

IsNot

'is not'

NotIn

'not in'

BinaryOr

'|'

Xor

'^'

BinaryAnd

'&'

ShiftLeft

'<<'

ShiftRight

'>>'

Multiply

'*'

Plus

'+'

Minus

'-'

Divide

'/'

FloorDivide

'//'

Invert

'~' (bitwise inversion of its integer argument)

Modulo

'%'

Dot

'.'

Instances

data Argument Source

Arguments to function calls, class declarations and decorators.

Constructors

ArgExpr

Ordinary argument expression.

Fields

arg_expr :: Expr
 
ArgVarArgsPos

Excess positional argument.

Fields

arg_expr :: Expr
 
ArgVarArgsKeyword

Excess keyword argument.

Fields

arg_expr :: Expr
 
ArgKeyword

Keyword argument.

Fields

arg_keyword :: Ident

Keyword name.

arg_expr :: Expr
 

Imports

data ImportItem Source

An entity imported using the 'import' keyword. See http://docs.python.org/dev/3.0/reference/simple_stmts.html#the-import-statement.

Constructors

ImportItem 

Fields

import_item_name :: DottedName

The name of module to import.

import_as_name :: Maybe Ident

An optional name to refer to the entity (the 'as' name).

data FromItem Source

An entity imported using the 'from ... import' construct. See http://docs.python.org/dev/3.0/reference/simple_stmts.html#the-import-statement

Constructors

FromItem 

Fields

from_item_name :: Ident

The name of the entity imported.

from_as_name :: Maybe Ident

An optional name to refer to the entity (the 'as' name).

data FromItems Source

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

Constructors

ImportEverything

Import everything exported from the module.

FromItems [FromItem]

Import a specific list of items from the module.

data ImportModule Source

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

Constructors

ImportRelative ImportModule

Relative import. A dot followed by something.

ImportDot

Relative import. Dot on its own.

ImportName DottedName

The name of the module to import from.

Exceptions

Comprehensions