|
| Language.Python.Common.AST | | Portability | ghc | | Stability | experimental | | Maintainer | bjpop@csse.unimelb.edu.au |
|
|
|
|
|
| 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
|
|
|
| Convenient access to annotations in annotated types.
| | | Methods | | annot :: t annot -> annot | Source |
| | Given an annotated type, project out its annotation value.
|
| | Instances | |
|
|
| Modules
|
|
|
A module (Python source file).
| | Constructors | | Module [Statement annot] | A module is just a sequence of top-level statements.
|
| Instances | |
|
|
|
|
| Identifiers and dotted names
|
|
|
| Identifier.
| | Constructors | | Ident | | | ident_string :: !String | | | ident_annot :: annot | |
|
| Instances | |
|
|
|
|
|
| A compound name constructed with the dot operator.
|
|
|
|
| Statements, suites, parameters, decorators and assignment operators
|
|
|
Statements.
| | Constructors | | Import | Import statement.
| | import_items :: [ImportItem annot] | Items to import.
| | stmt_annot :: annot | |
| | FromImport | From ... import statement.
| | from_module :: ImportRelative annot | Module to import from.
| | from_items :: FromItems annot | Items to import.
| | stmt_annot :: annot | |
| | While | While loop.
| | while_cond :: Expr annot | Loop condition.
| | while_body :: Suite annot | Loop body.
| | while_else :: Suite annot | Else clause.
| | stmt_annot :: annot | |
| | For | For loop.
| | 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.
| | 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.
| | 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).
| | 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.
| | assign_to :: [Expr annot] | Entity to assign to.
| | assign_expr :: Expr annot | Expression to evaluate.
| | stmt_annot :: annot | |
| | AugmentedAssign | Augmented assignment statement.
| | 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.
| | 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).
| | return_expr :: Maybe (Expr annot) | Optional expression to evaluate and return to caller.
| | stmt_annot :: annot | |
| | Try | Try statement (exception handling).
| | 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).
| | raise_expr :: RaiseExpr annot | | | stmt_annot :: annot | |
| | With | With statement (context management).
| | 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).
| | | 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).
| | | 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).
| | | Delete | Del statement (delete).
| | del_exprs :: [Expr annot] | Items to delete.
| | stmt_annot :: annot | |
| | StmtExpr | Expression statement.
| | stmt_expr :: Expr annot | | | stmt_annot :: annot | |
| | Global | Global declaration.
| | global_vars :: [Ident annot] | Variables declared global in the current block.
| | stmt_annot :: annot | |
| | NonLocal | Nonlocal 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 | |
| | Assert | Assertion.
| | assert_exprs :: [Expr annot] | Expressions being asserted.
| | stmt_annot :: annot | |
| | Print | Print statement. Version 2 only.
| | 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.
| | 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 | |
|
|
|
|
|
A block of statements. A suite is a group of statements controlled by a clause,
for example, the body of a loop.
|
|
|
|
|
Formal parameter of function definitions and lambda expressions.
| | Constructors | | Param | Ordinary named parameter.
| | 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).
| | 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).
| | 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).
| | | UnPackTuple | Tuple unpack. Version 2 only.
| | param_unpack_tuple :: ParamTuple annot | The tuple to unpack.
| | param_default :: Maybe (Expr annot) | Optional default value.
| | param_annot :: annot | |
|
| Instances | |
|
|
|
|
|
| Tuple unpack parameter. Version 2 only.
| | Constructors | | ParamTupleName | A variable name.
| | param_tuple_name :: Ident annot | | | param_tuple_annot :: annot | |
| | ParamTuple | A (possibly nested) tuple parameter.
| | param_tuple :: [ParamTuple annot] | | | param_tuple_annot :: annot | |
|
| Instances | |
|
|
|
|
|
| Decorator.
| | Constructors | | Decorator | | | decorator_name :: DottedName annot | Decorator name.
| | decorator_args :: [Argument annot] | Decorator arguments.
| | decorator_annot :: annot | |
|
| Instances | |
|
|
|
|
|
| Augmented assignment operators.
| | Constructors | | PlusAssign | '+='
| | | MinusAssign | '-='
| | | MultAssign | '*='
| | | DivAssign | '/='
| | | ModAssign | '%='
| | | PowAssign | '*='
| | | BinAndAssign | '&='
| | | BinOrAssign | '|='
| | | BinXorAssign | '^='
| | | LeftShiftAssign | '<<='
| | | RightShiftAssign | '>>='
| | | FloorDivAssign | '//='
| |
| Instances | |
|
|
|
|
| Expressions, operators, arguments and slices
|
|
|
Expressions.
| | Constructors | | Var | Variable.
| | var_ident :: Ident annot | | | expr_annot :: annot | |
| | Int | Literal integer.
| | | LongInt | Long literal integer. Version 2 only.
| | | Float | Literal floating point number.
| | float_value :: Double | | | expr_literal :: String | | | expr_annot :: annot | |
| | Imaginary | Literal imaginary number.
| | imaginary_value :: Double | | | expr_literal :: String | | | expr_annot :: annot | |
| | Bool | Literal boolean.
| | bool_value :: Bool | | | expr_annot :: annot | |
| | None | Literal 'None' value.
| | | Ellipsis | Ellipsis '...'.
| | | ByteStrings | Literal byte string.
| | byte_string_strings :: [String] | | | expr_annot :: annot | |
| | Strings | Literal strings (to be concatentated together).
| | strings_strings :: [String] | | | expr_annot :: annot | |
| | Call | Function call.
| | 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]'.
| | subscriptee :: Expr annot | | | subscript_exprs :: [Expr annot] | | | expr_annot :: annot | |
| | SlicedExpr | Slicing, for example 'w [x:y:z]'.
| | slicee :: Expr annot | | | slices :: [Slice annot] | | | expr_annot :: annot | |
| | CondExpr | Conditional expresison.
| | 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.
| | operator :: Op annot | | | left_op_arg :: Expr annot | | | right_op_arg :: Expr annot | | | expr_annot :: annot | |
| | UnaryOp | Unary operator application.
| | operator :: Op annot | | | op_arg :: Expr annot | | | expr_annot :: annot | |
| | Lambda | Anonymous function definition (lambda).
| | lambda_args :: [Parameter annot] | | | lambda_body :: Expr annot | | | expr_annot :: annot | |
| | Tuple | Tuple. Can be empty.
| | tuple_exprs :: [Expr annot] | | | expr_annot :: annot | |
| | Yield | Generator yield.
| | yield_expr :: Maybe (Expr annot) | Optional expression to yield.
| | expr_annot :: annot | |
| | Generator | Generator.
| | | ListComp | List comprehension.
| | | List | List.
| | list_exprs :: [Expr annot] | | | expr_annot :: annot | |
| | Dictionary | Dictionary.
| | dict_mappings :: [(Expr annot, Expr annot)] | | | expr_annot :: annot | |
| | DictComp | Dictionary comprehension. Version 3 only.
| | | Set | Set.
| | set_exprs :: [Expr annot] | | | expr_annot :: annot | |
| | SetComp | Set comprehension. Version 3 only.
| | | Starred | Starred expression. Version 3 only.
| | starred_expr :: Expr annot | | | expr_annot :: annot | |
| | Paren | Parenthesised expression.
| | paren_expr :: Expr annot | | | expr_annot :: annot | |
| | StringConversion | String conversion (backquoted expression). Version 2 only.
| | backquoted_expr :: Expr annot | | | expr_anot :: annot | |
|
| Instances | |
|
|
|
|
|
| Operators.
| | Constructors | | And | 'and'
| | | Or | 'or'
| | | Not | 'not'
| | | Exponent | '**'
| | | LessThan | '<'
| | | GreaterThan | '>'
| | | Equality | '=='
| | | GreaterThanEquals | '>='
| | | LessThanEquals | '<='
| | | NotEquals | '!='
| | | NotEqualsV2 | ''. Version 2 only.
| | | 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 | |
|
|
|
|
|
| Arguments to function calls, class declarations and decorators.
| | Constructors | | ArgExpr | Ordinary argument expression.
| | arg_expr :: Expr annot | | | arg_annot :: annot | |
| | ArgVarArgsPos | Excess positional argument.
| | arg_expr :: Expr annot | | | arg_annot :: annot | |
| | ArgVarArgsKeyword | Excess keyword argument.
| | arg_expr :: Expr annot | | | arg_annot :: annot | |
| | ArgKeyword | Keyword argument.
| | arg_keyword :: Ident annot | Keyword name.
| | arg_expr :: Expr annot | Argument expression.
| | arg_annot :: annot | |
|
| Instances | |
|
|
|
|
|
| Slice compenent.
| | Constructors | | SliceProper | | | | SliceExpr | | | slice_expr :: Expr annot | | | slice_annot :: annot | |
| | SliceEllipsis | | |
| Instances | |
|
|
|
|
| Imports
|
|
|
An entity imported using the 'import' keyword.
| | Constructors | | ImportItem | | | 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 | |
|
|
|
|
|
An entity imported using the 'from ... import' construct.
| | Constructors | | FromItem | | | 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 | |
|
|
|
|
|
| Items imported using the 'from ... import' construct.
| | Constructors | | ImportEverything | Import everything exported from the module.
| | from_items_annot :: annot | |
| | FromItems | Import a specific list of items from the module.
| | 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.
| | Constructors | | ImportRelative | | | import_relative_dots :: Int | | | import_relative_module :: Maybe (DottedName annot) | | | import_relative_annot :: annot | |
|
| Instances | |
|
|
|
|
| Exceptions
|
|
|
| Exception handler.
| | Constructors | | Handler | | | handler_clause :: ExceptClause annot | | | handler_suite :: Suite annot | | | handler_annot :: annot | |
|
| Instances | |
|
|
|
|
| data ExceptClause annot | Source |
|
| Exception clause.
| | Constructors | | Instances | |
|
|
|
|
|
| The argument for a raise statement.
| | Constructors | | Instances | |
|
|
|
|
| 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 | |
|
| Instances | |
|
|
|
|
|
| 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 | |
|
| Instances | |
|
|
|
|
|
| Comprehension guard.
| | Constructors | | Instances | |
|
|
|
|
|
| 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 | |
|
| Instances | |
|
|
|
|
| Produced by Haddock version 2.4.2 |