language-python-0.5.3: 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.

Minimal complete definition

annot

Methods

annot :: t annot -> annot Source #

Given an annotated type, project out its annotation value.

Instances

Annotated AssignOp Source # 

Methods

annot :: AssignOp annot -> annot Source #

Annotated Op Source # 

Methods

annot :: Op annot -> annot Source #

Annotated Slice Source # 

Methods

annot :: Slice annot -> annot Source #

Annotated Expr Source # 

Methods

annot :: Expr annot -> annot Source #

Annotated CompIter Source # 

Methods

annot :: CompIter annot -> annot Source #

Annotated CompIf Source # 

Methods

annot :: CompIf annot -> annot Source #

Annotated CompFor Source # 

Methods

annot :: CompFor annot -> annot Source #

Annotated Comprehension Source # 

Methods

annot :: Comprehension annot -> annot Source #

Annotated ExceptClause Source # 

Methods

annot :: ExceptClause annot -> annot Source #

Annotated Handler Source # 

Methods

annot :: Handler annot -> annot Source #

Annotated Argument Source # 

Methods

annot :: Argument annot -> annot Source #

Annotated ParamTuple Source # 

Methods

annot :: ParamTuple annot -> annot Source #

Annotated Parameter Source # 

Methods

annot :: Parameter annot -> annot Source #

Annotated Decorator Source # 

Methods

annot :: Decorator annot -> annot Source #

Annotated Statement Source # 

Methods

annot :: Statement annot -> annot Source #

Annotated ImportRelative Source # 

Methods

annot :: ImportRelative annot -> annot Source #

Annotated FromItems Source # 

Methods

annot :: FromItems annot -> annot Source #

Annotated FromItem Source # 

Methods

annot :: FromItem annot -> annot Source #

Annotated ImportItem Source # 

Methods

annot :: ImportItem annot -> annot Source #

Annotated Ident Source # 

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 # 

Methods

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

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

Eq annot => Eq (Module annot) Source # 

Methods

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

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

Data annot => Data (Module annot) Source # 

Methods

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

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

toConstr :: Module annot -> Constr #

dataTypeOf :: Module annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (Module annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (Module annot) Source # 

Methods

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

show :: Module annot -> String #

showList :: [Module annot] -> ShowS #

Identifiers and dotted names

data Ident annot Source #

Identifier.

Constructors

Ident 

Fields

Instances

Functor Ident Source # 

Methods

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

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

Span IdentSpan Source # 
Annotated Ident Source # 

Methods

annot :: Ident annot -> annot Source #

Eq annot => Eq (Ident annot) Source # 

Methods

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

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

Data annot => Data (Ident annot) Source # 

Methods

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

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

toConstr :: Ident annot -> Constr #

dataTypeOf :: Ident annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (Ident annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (Ident annot) Source # 

Methods

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

show :: Ident annot -> String #

showList :: [Ident annot] -> ShowS #

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

Fun

Function definition.

Fields

Class

Class definition.

Fields

Conditional

Conditional statement (if-elif-else).

Fields

Assign

Assignment statement.

Fields

AugmentedAssign

Augmented assignment statement.

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

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 # 

Methods

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

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

Span StatementSpan Source # 
Annotated Statement Source # 

Methods

annot :: Statement annot -> annot Source #

Eq annot => Eq (Statement annot) Source # 

Methods

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

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

Data annot => Data (Statement annot) Source # 

Methods

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

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

toConstr :: Statement annot -> Constr #

dataTypeOf :: Statement annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (Statement annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (Statement annot) Source # 

Methods

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

show :: Statement annot -> String #

showList :: [Statement annot] -> ShowS #

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 # 

Methods

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

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

Span ParameterSpan Source # 
Annotated Parameter Source # 

Methods

annot :: Parameter annot -> annot Source #

Eq annot => Eq (Parameter annot) Source # 

Methods

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

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

Data annot => Data (Parameter annot) Source # 

Methods

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

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

toConstr :: Parameter annot -> Constr #

dataTypeOf :: Parameter annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (Parameter annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (Parameter annot) Source # 

Methods

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

show :: Parameter annot -> String #

showList :: [Parameter annot] -> ShowS #

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 # 

Methods

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

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

Span ParamTupleSpan Source # 
Annotated ParamTuple Source # 

Methods

annot :: ParamTuple annot -> annot Source #

Eq annot => Eq (ParamTuple annot) Source # 

Methods

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

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

Data annot => Data (ParamTuple annot) Source # 

Methods

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

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

toConstr :: ParamTuple annot -> Constr #

dataTypeOf :: ParamTuple annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (ParamTuple annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (ParamTuple annot) Source # 

Methods

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

show :: ParamTuple annot -> String #

showList :: [ParamTuple annot] -> ShowS #

data Decorator annot Source #

Decorator.

Constructors

Decorator 

Fields

Instances

Functor Decorator Source # 

Methods

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

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

Span DecoratorSpan Source # 
Annotated Decorator Source # 

Methods

annot :: Decorator annot -> annot Source #

Eq annot => Eq (Decorator annot) Source # 

Methods

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

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

Data annot => Data (Decorator annot) Source # 

Methods

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

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

toConstr :: Decorator annot -> Constr #

dataTypeOf :: Decorator annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (Decorator annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (Decorator annot) Source # 

Methods

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

show :: Decorator annot -> String #

showList :: [Decorator annot] -> ShowS #

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

Instances

Functor AssignOp Source # 

Methods

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

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

Span AssignOpSpan Source # 
Annotated AssignOp Source # 

Methods

annot :: AssignOp annot -> annot Source #

Eq annot => Eq (AssignOp annot) Source # 

Methods

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

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

Data annot => Data (AssignOp annot) Source # 

Methods

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

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

toConstr :: AssignOp annot -> Constr #

dataTypeOf :: AssignOp annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (AssignOp annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (AssignOp annot) Source # 

Methods

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

show :: AssignOp annot -> String #

showList :: [AssignOp annot] -> ShowS #

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

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 # 

Methods

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

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

Span ExprSpan Source # 
Annotated Expr Source # 

Methods

annot :: Expr annot -> annot Source #

Eq annot => Eq (Expr annot) Source # 

Methods

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

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

Data annot => Data (Expr annot) Source # 

Methods

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

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

toConstr :: Expr annot -> Constr #

dataTypeOf :: Expr annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (Expr annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (Expr annot) Source # 

Methods

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

show :: Expr annot -> String #

showList :: [Expr annot] -> ShowS #

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

Invert

'~' (bitwise inversion of its integer argument)

Fields

Modulo

'%'

Fields

Instances

Functor Op Source # 

Methods

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

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

Span OpSpan Source # 
Annotated Op Source # 

Methods

annot :: Op annot -> annot Source #

Eq annot => Eq (Op annot) Source # 

Methods

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

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

Data annot => Data (Op annot) Source # 

Methods

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

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

toConstr :: Op annot -> Constr #

dataTypeOf :: Op annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (Op annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (Op annot) Source # 

Methods

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

show :: Op annot -> String #

showList :: [Op annot] -> ShowS #

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 # 

Methods

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

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

Span ArgumentSpan Source # 
Annotated Argument Source # 

Methods

annot :: Argument annot -> annot Source #

Eq annot => Eq (Argument annot) Source # 

Methods

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

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

Data annot => Data (Argument annot) Source # 

Methods

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

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

toConstr :: Argument annot -> Constr #

dataTypeOf :: Argument annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (Argument annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (Argument annot) Source # 

Methods

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

show :: Argument annot -> String #

showList :: [Argument annot] -> ShowS #

data Slice annot Source #

Slice compenent.

Constructors

SliceProper 

Fields

SliceExpr 

Fields

SliceEllipsis 

Fields

Instances

Functor Slice Source # 

Methods

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

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

Span SliceSpan Source # 
Annotated Slice Source # 

Methods

annot :: Slice annot -> annot Source #

Eq annot => Eq (Slice annot) Source # 

Methods

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

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

Data annot => Data (Slice annot) Source # 

Methods

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

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

toConstr :: Slice annot -> Constr #

dataTypeOf :: Slice annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (Slice annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (Slice annot) Source # 

Methods

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

show :: Slice annot -> String #

showList :: [Slice annot] -> ShowS #

data DictMappingPair annot Source #

Constructors

DictMappingPair (Expr annot) (Expr annot) 

Instances

Functor DictMappingPair Source # 

Methods

fmap :: (a -> b) -> DictMappingPair a -> DictMappingPair b #

(<$) :: a -> DictMappingPair b -> DictMappingPair a #

Span DictMappingPairSpan Source # 
Eq annot => Eq (DictMappingPair annot) Source # 

Methods

(==) :: DictMappingPair annot -> DictMappingPair annot -> Bool #

(/=) :: DictMappingPair annot -> DictMappingPair annot -> Bool #

Data annot => Data (DictMappingPair annot) Source # 

Methods

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

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

toConstr :: DictMappingPair annot -> Constr #

dataTypeOf :: DictMappingPair annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (DictMappingPair annot) Source # 
Show annot => Show (DictMappingPair annot) Source # 

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 # 

Methods

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

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

Span YieldArgSpan Source # 
Eq annot => Eq (YieldArg annot) Source # 

Methods

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

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

Data annot => Data (YieldArg annot) Source # 

Methods

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

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

toConstr :: YieldArg annot -> Constr #

dataTypeOf :: YieldArg annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (YieldArg annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (YieldArg annot) Source # 

Methods

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

show :: YieldArg annot -> String #

showList :: [YieldArg annot] -> ShowS #

Imports

data ImportItem annot Source #

Constructors

ImportItem 

Fields

Instances

Functor ImportItem Source # 

Methods

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

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

Span ImportItemSpan Source # 
Annotated ImportItem Source # 

Methods

annot :: ImportItem annot -> annot Source #

Eq annot => Eq (ImportItem annot) Source # 

Methods

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

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

Data annot => Data (ImportItem annot) Source # 

Methods

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

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

toConstr :: ImportItem annot -> Constr #

dataTypeOf :: ImportItem annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (ImportItem annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (ImportItem annot) Source # 

Methods

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

show :: ImportItem annot -> String #

showList :: [ImportItem annot] -> ShowS #

data FromItem annot Source #

Constructors

FromItem 

Fields

Instances

Functor FromItem Source # 

Methods

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

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

Span FromItemSpan Source # 
Annotated FromItem Source # 

Methods

annot :: FromItem annot -> annot Source #

Eq annot => Eq (FromItem annot) Source # 

Methods

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

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

Data annot => Data (FromItem annot) Source # 

Methods

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

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

toConstr :: FromItem annot -> Constr #

dataTypeOf :: FromItem annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (FromItem annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (FromItem annot) Source # 

Methods

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

show :: FromItem annot -> String #

showList :: [FromItem annot] -> ShowS #

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 # 

Methods

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

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

Span FromItemsSpan Source # 
Annotated FromItems Source # 

Methods

annot :: FromItems annot -> annot Source #

Eq annot => Eq (FromItems annot) Source # 

Methods

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

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

Data annot => Data (FromItems annot) Source # 

Methods

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

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

toConstr :: FromItems annot -> Constr #

dataTypeOf :: FromItems annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (FromItems annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (FromItems annot) Source # 

Methods

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

show :: FromItems annot -> String #

showList :: [FromItems annot] -> ShowS #

data ImportRelative annot Source #

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

Instances

Functor ImportRelative Source # 

Methods

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

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

Span ImportRelativeSpan Source # 
Annotated ImportRelative Source # 

Methods

annot :: ImportRelative annot -> annot Source #

Eq annot => Eq (ImportRelative annot) Source # 

Methods

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

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

Data annot => Data (ImportRelative annot) Source # 

Methods

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

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

toConstr :: ImportRelative annot -> Constr #

dataTypeOf :: ImportRelative annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (ImportRelative annot) Source # 

Methods

compare :: ImportRelative annot -> ImportRelative annot -> Ordering #

(<) :: ImportRelative annot -> ImportRelative annot -> Bool #

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

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

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

max :: ImportRelative annot -> ImportRelative annot -> ImportRelative annot #

min :: ImportRelative annot -> ImportRelative annot -> ImportRelative annot #

Show annot => Show (ImportRelative annot) Source # 

Methods

showsPrec :: Int -> ImportRelative annot -> ShowS #

show :: ImportRelative annot -> String #

showList :: [ImportRelative annot] -> ShowS #

Exceptions

data Handler annot Source #

Exception handler.

Constructors

Handler 

Fields

Instances

Functor Handler Source # 

Methods

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

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

Span HandlerSpan Source # 
Annotated Handler Source # 

Methods

annot :: Handler annot -> annot Source #

Eq annot => Eq (Handler annot) Source # 

Methods

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

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

Data annot => Data (Handler annot) Source # 

Methods

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

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

toConstr :: Handler annot -> Constr #

dataTypeOf :: Handler annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (Handler annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (Handler annot) Source # 

Methods

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

show :: Handler annot -> String #

showList :: [Handler annot] -> ShowS #

data ExceptClause annot Source #

Exception clause.

Constructors

ExceptClause 

Fields

Instances

Functor ExceptClause Source # 

Methods

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

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

Span ExceptClauseSpan Source # 
Annotated ExceptClause Source # 

Methods

annot :: ExceptClause annot -> annot Source #

Eq annot => Eq (ExceptClause annot) Source # 

Methods

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

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

Data annot => Data (ExceptClause annot) Source # 

Methods

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

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

toConstr :: ExceptClause annot -> Constr #

dataTypeOf :: ExceptClause annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (ExceptClause annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (ExceptClause annot) Source # 

Methods

showsPrec :: Int -> ExceptClause annot -> ShowS #

show :: ExceptClause annot -> String #

showList :: [ExceptClause annot] -> ShowS #

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 # 

Methods

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

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

Eq annot => Eq (RaiseExpr annot) Source # 

Methods

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

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

Data annot => Data (RaiseExpr annot) Source # 

Methods

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

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

toConstr :: RaiseExpr annot -> Constr #

dataTypeOf :: RaiseExpr annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (RaiseExpr annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (RaiseExpr annot) Source # 

Methods

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

show :: RaiseExpr annot -> String #

showList :: [RaiseExpr annot] -> ShowS #

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 # 

Methods

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

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

Span ComprehensionSpan Source # 
Annotated Comprehension Source # 

Methods

annot :: Comprehension annot -> annot Source #

Eq annot => Eq (Comprehension annot) Source # 

Methods

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

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

Data annot => Data (Comprehension annot) Source # 

Methods

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

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

toConstr :: Comprehension annot -> Constr #

dataTypeOf :: Comprehension annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (Comprehension annot) Source # 

Methods

compare :: Comprehension annot -> Comprehension annot -> Ordering #

(<) :: Comprehension annot -> Comprehension annot -> Bool #

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

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

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

max :: Comprehension annot -> Comprehension annot -> Comprehension annot #

min :: Comprehension annot -> Comprehension annot -> Comprehension annot #

Show annot => Show (Comprehension annot) Source # 

Methods

showsPrec :: Int -> Comprehension annot -> ShowS #

show :: Comprehension annot -> String #

showList :: [Comprehension annot] -> ShowS #

data ComprehensionExpr annot Source #

Instances

Functor ComprehensionExpr Source # 
Span ComprehensionExprSpan Source # 
Eq annot => Eq (ComprehensionExpr annot) Source # 
Data annot => Data (ComprehensionExpr annot) Source # 

Methods

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

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

toConstr :: ComprehensionExpr annot -> Constr #

dataTypeOf :: ComprehensionExpr annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (ComprehensionExpr annot) Source # 
Show annot => Show (ComprehensionExpr annot) Source # 

data CompFor annot Source #

Comprehension 'for' component.

Constructors

CompFor 

Fields

Instances

Functor CompFor Source # 

Methods

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

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

Span CompForSpan Source # 
Annotated CompFor Source # 

Methods

annot :: CompFor annot -> annot Source #

Eq annot => Eq (CompFor annot) Source # 

Methods

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

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

Data annot => Data (CompFor annot) Source # 

Methods

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

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

toConstr :: CompFor annot -> Constr #

dataTypeOf :: CompFor annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (CompFor annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (CompFor annot) Source # 

Methods

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

show :: CompFor annot -> String #

showList :: [CompFor annot] -> ShowS #

data CompIf annot Source #

Comprehension guard.

Constructors

CompIf 

Fields

Instances

Functor CompIf Source # 

Methods

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

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

Span CompIfSpan Source # 
Annotated CompIf Source # 

Methods

annot :: CompIf annot -> annot Source #

Eq annot => Eq (CompIf annot) Source # 

Methods

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

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

Data annot => Data (CompIf annot) Source # 

Methods

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

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

toConstr :: CompIf annot -> Constr #

dataTypeOf :: CompIf annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (CompIf annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (CompIf annot) Source # 

Methods

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

show :: CompIf annot -> String #

showList :: [CompIf annot] -> ShowS #

data CompIter annot Source #

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

Constructors

IterFor 

Fields

IterIf 

Fields

Instances

Functor CompIter Source # 

Methods

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

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

Span CompIterSpan Source # 
Annotated CompIter Source # 

Methods

annot :: CompIter annot -> annot Source #

Eq annot => Eq (CompIter annot) Source # 

Methods

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

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

Data annot => Data (CompIter annot) Source # 

Methods

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

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

toConstr :: CompIter annot -> Constr #

dataTypeOf :: CompIter annot -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord annot => Ord (CompIter annot) Source # 

Methods

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

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

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

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

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

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

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

Show annot => Show (CompIter annot) Source # 

Methods

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

show :: CompIter annot -> String #

showList :: [CompIter annot] -> ShowS #