{-# LANGUAGE FlexibleInstances, TypeSynonymInstances, CPP, DeriveDataTypeable, DeriveFunctor #-}
module Language.Python.Common.AST (
Annotated (..)
, Module (..), ModuleSpan
, Ident (..), IdentSpan
, DottedName, DottedNameSpan
, Statement (..), StatementSpan
, Suite, SuiteSpan
, Parameter (..), ParameterSpan
, ParamTuple (..), ParamTupleSpan
, Decorator (..), DecoratorSpan
, AssignOp (..), AssignOpSpan
, Expr (..), ExprSpan
, Op (..), OpSpan
, Argument (..), ArgumentSpan
, Slice (..), SliceSpan
, DictKeyDatumList (..), DictKeyDatumListSpan
, YieldArg (..), YieldArgSpan
, ImportItem (..), ImportItemSpan
, FromItem (..), FromItemSpan
, FromItems (..), FromItemsSpan
, ImportRelative (..), ImportRelativeSpan
, Handler (..), HandlerSpan
, ExceptClause (..), ExceptClauseSpan
, RaiseExpr (..), RaiseExprSpan
, Comprehension (..), ComprehensionSpan
, ComprehensionExpr (..), ComprehensionExprSpan
, CompFor (..), CompForSpan
, CompIf (..), CompIfSpan
, CompIter (..), CompIterSpan
)
where
import Language.Python.Common.SrcLocation ( Span (getSpan), SrcSpan (..), spanning )
import Data.Data
class Annotated t where
annot :: t annot -> annot
data Ident annot = Ident { ident_string :: !String, ident_annot :: annot }
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type IdentSpan = Ident SrcSpan
instance Span IdentSpan where
getSpan = annot
instance Annotated Ident where
annot = ident_annot
newtype Module annot = Module [Statement annot]
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type ModuleSpan = Module SrcSpan
type Suite annot = [Statement annot]
type SuiteSpan = Suite SrcSpan
type DottedName annot = [Ident annot]
type DottedNameSpan = DottedName SrcSpan
data ImportItem annot =
ImportItem
{ import_item_name :: DottedName annot
, import_as_name :: Maybe (Ident annot)
, import_item_annot :: annot
}
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type ImportItemSpan = ImportItem SrcSpan
instance Span ImportItemSpan where
getSpan = annot
instance Annotated ImportItem where
annot = import_item_annot
data FromItem annot =
FromItem
{ from_item_name :: Ident annot
, from_as_name :: Maybe (Ident annot)
, from_item_annot :: annot
}
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type FromItemSpan = FromItem SrcSpan
instance Span FromItemSpan where
getSpan = annot
instance Annotated FromItem where
annot = from_item_annot
data FromItems annot
= ImportEverything { from_items_annot :: annot }
| FromItems { from_items_items :: [FromItem annot], from_items_annot :: annot }
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type FromItemsSpan = FromItems SrcSpan
instance Span FromItemsSpan where
getSpan = annot
instance Annotated FromItems where
annot = from_items_annot
data ImportRelative annot
= ImportRelative
{ import_relative_dots :: Int
, import_relative_module :: Maybe (DottedName annot)
, import_relative_annot :: annot
}
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type ImportRelativeSpan = ImportRelative SrcSpan
instance Span ImportRelativeSpan where
getSpan = annot
instance Annotated ImportRelative where
annot = import_relative_annot
data Statement annot
= Import
{ import_items :: [ImportItem annot]
, stmt_annot :: annot
}
| FromImport
{ from_module :: ImportRelative annot
, from_items :: FromItems annot
, stmt_annot :: annot
}
| While
{ while_cond :: Expr annot
, while_body :: Suite annot
, while_else :: Suite annot
, stmt_annot :: annot
}
| For
{ for_targets :: [Expr annot]
, for_generator :: Expr annot
, for_body :: Suite annot
, for_else :: Suite annot
, stmt_annot :: annot
}
| AsyncFor
{ for_stmt :: Statement annot
, stmt_annot :: annot
}
| Fun
{ fun_name :: Ident annot
, fun_args :: [Parameter annot]
, fun_result_annotation :: Maybe (Expr annot)
, fun_body :: Suite annot
, stmt_annot :: annot
}
| AsyncFun
{ fun_def :: Statement annot
, stmt_annot :: annot
}
| Class
{ class_name :: Ident annot
, class_args :: [Argument annot]
, class_body :: Suite annot
, stmt_annot :: annot
}
| Conditional
{ cond_guards :: [(Expr annot, Suite annot)]
, cond_else :: Suite annot
, stmt_annot :: annot
}
| Assign
{ assign_to :: [Expr annot]
, assign_expr :: Expr annot
, stmt_annot :: annot
}
| AugmentedAssign
{ aug_assign_to :: Expr annot
, aug_assign_op :: AssignOp annot
, aug_assign_expr :: Expr annot
, stmt_annot :: annot
}
| AnnotatedAssign
{ ann_assign_annotation :: Expr annot
, ann_assign_to :: Expr annot
, ann_assign_expr :: Maybe (Expr annot)
, stmt_annot :: annot
}
| Decorated
{ decorated_decorators :: [Decorator annot]
, decorated_def :: Statement annot
, stmt_annot :: annot
}
| Return
{ return_expr :: Maybe (Expr annot)
, stmt_annot :: annot
}
| Try
{ try_body :: Suite annot
, try_excepts :: [Handler annot]
, try_else :: Suite annot
, try_finally :: Suite annot
, stmt_annot :: annot
}
| Raise
{ raise_expr :: RaiseExpr annot
, stmt_annot :: annot
}
| With
{ with_context :: [(Expr annot, Maybe (Expr annot))]
, with_body :: Suite annot
, stmt_annot :: annot
}
| AsyncWith
{ with_stmt :: Statement annot
, stmt_annot :: annot
}
| Pass { stmt_annot :: annot }
| Break { stmt_annot :: annot }
| Continue { stmt_annot :: annot }
| Delete
{ del_exprs :: [Expr annot]
, stmt_annot :: annot
}
| StmtExpr { stmt_expr :: Expr annot, stmt_annot :: annot }
| Global
{ global_vars :: [Ident annot]
, stmt_annot :: annot
}
| NonLocal
{ nonLocal_vars :: [Ident annot]
, stmt_annot :: annot
}
| Assert
{ assert_exprs :: [Expr annot]
, stmt_annot :: annot
}
| Print
{ print_chevron :: Bool
, print_exprs :: [Expr annot]
, print_trailing_comma :: Bool
, stmt_annot :: annot
}
| Exec
{ exec_expr :: Expr annot
, exec_globals_locals :: Maybe (Expr annot, Maybe (Expr annot))
, stmt_annot :: annot
}
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type StatementSpan = Statement SrcSpan
instance Span StatementSpan where
getSpan = annot
instance Annotated Statement where
annot = stmt_annot
data RaiseExpr annot
= RaiseV3 (Maybe (Expr annot, Maybe (Expr annot)))
| RaiseV2 (Maybe (Expr annot, (Maybe (Expr annot, Maybe (Expr annot)))))
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type RaiseExprSpan = RaiseExpr SrcSpan
data Decorator annot =
Decorator
{ decorator_name :: DottedName annot
, decorator_args :: [Argument annot]
, decorator_annot :: annot
}
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type DecoratorSpan = Decorator SrcSpan
instance Span DecoratorSpan where
getSpan = annot
instance Annotated Decorator where
annot = decorator_annot
data Parameter annot
= Param
{ param_name :: Ident annot
, param_py_annotation :: Maybe (Expr annot)
, param_default :: Maybe (Expr annot)
, param_annot :: annot
}
| VarArgsPos
{ param_name :: Ident annot
, param_py_annotation :: Maybe (Expr annot)
, param_annot :: annot
}
| VarArgsKeyword
{ param_name :: Ident annot
, param_py_annotation :: Maybe (Expr annot)
, param_annot :: annot
}
| EndPositional { param_annot :: annot }
| UnPackTuple
{ param_unpack_tuple :: ParamTuple annot
, param_default :: Maybe (Expr annot)
, param_annot :: annot
}
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type ParameterSpan = Parameter SrcSpan
instance Span ParameterSpan where
getSpan = annot
instance Annotated Parameter where
annot = param_annot
data ParamTuple annot
= ParamTupleName { param_tuple_name :: Ident annot, param_tuple_annot :: annot }
| ParamTuple { param_tuple :: [ParamTuple annot], param_tuple_annot :: annot }
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type ParamTupleSpan = ParamTuple SrcSpan
instance Span ParamTupleSpan where
getSpan = annot
instance Annotated ParamTuple where
annot = param_tuple_annot
data Argument annot
= ArgExpr { arg_expr :: Expr annot, arg_annot :: annot }
| ArgVarArgsPos { arg_expr :: Expr annot, arg_annot :: annot }
| ArgVarArgsKeyword { arg_expr :: Expr annot, arg_annot :: annot }
| ArgKeyword
{ arg_keyword :: Ident annot
, arg_expr :: Expr annot
, arg_annot :: annot
}
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type ArgumentSpan = Argument SrcSpan
instance Span ArgumentSpan where
getSpan = annot
instance Annotated Argument where
annot = arg_annot
data Handler annot
= Handler
{ handler_clause :: ExceptClause annot
, handler_suite :: Suite annot
, handler_annot :: annot
}
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type HandlerSpan = Handler SrcSpan
instance Span HandlerSpan where
getSpan = annot
instance Annotated Handler where
annot = handler_annot
data ExceptClause annot
= ExceptClause
{ except_clause :: Maybe (Expr annot, Maybe (Expr annot))
, except_clause_annot :: annot
}
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type ExceptClauseSpan = ExceptClause SrcSpan
instance Span ExceptClauseSpan where
getSpan = annot
instance Annotated ExceptClause where
annot = except_clause_annot
data Comprehension annot
= Comprehension
{ comprehension_expr :: ComprehensionExpr annot
, comprehension_for :: CompFor annot
, comprehension_annot :: annot
}
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type ComprehensionSpan = Comprehension SrcSpan
instance Span ComprehensionSpan where
getSpan = annot
instance Annotated Comprehension where
annot = comprehension_annot
data ComprehensionExpr annot
= ComprehensionExpr (Expr annot)
| ComprehensionDict (DictKeyDatumList annot)
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type ComprehensionExprSpan = ComprehensionExpr SrcSpan
instance Span ComprehensionExprSpan where
getSpan (ComprehensionExpr e) = getSpan e
getSpan (ComprehensionDict d) = getSpan d
data CompFor annot =
CompFor
{ comp_for_async :: Bool
, comp_for_exprs :: [Expr annot]
, comp_in_expr :: Expr annot
, comp_for_iter :: Maybe (CompIter annot)
, comp_for_annot :: annot
}
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type CompForSpan = CompFor SrcSpan
instance Span CompForSpan where
getSpan = annot
instance Annotated CompFor where
annot = comp_for_annot
data CompIf annot =
CompIf
{ comp_if :: Expr annot
, comp_if_iter :: Maybe (CompIter annot)
, comp_if_annot :: annot
}
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type CompIfSpan = CompIf SrcSpan
instance Span CompIfSpan where
getSpan = annot
instance Annotated CompIf where
annot = comp_if_annot
data CompIter annot
= IterFor { comp_iter_for :: CompFor annot, comp_iter_annot :: annot }
| IterIf { comp_iter_if :: CompIf annot, comp_iter_annot :: annot }
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type CompIterSpan = CompIter SrcSpan
instance Span CompIterSpan where
getSpan = annot
instance Annotated CompIter where
annot = comp_iter_annot
data Expr annot
= Var { var_ident :: Ident annot, expr_annot :: annot }
| Int { int_value :: Integer, expr_literal :: String, expr_annot :: annot }
| LongInt { int_value :: Integer, expr_literal :: String, expr_annot :: annot }
| Float { float_value :: Double, expr_literal :: String, expr_annot :: annot }
| Imaginary { imaginary_value :: Double, expr_literal :: String, expr_annot :: annot }
| Bool { bool_value :: Bool, expr_annot :: annot }
| None { expr_annot :: annot }
| Ellipsis { expr_annot :: annot }
| ByteStrings { byte_string_strings :: [String], expr_annot :: annot }
| Strings { strings_strings :: [String], expr_annot :: annot }
| UnicodeStrings { unicodestrings_strings :: [String], expr_annot :: annot }
| Call
{ call_fun :: Expr annot
, call_args :: [Argument annot]
, expr_annot :: annot
}
| Subscript { subscriptee :: Expr annot, subscript_expr :: Expr annot, expr_annot :: annot }
| SlicedExpr { slicee :: Expr annot, slices :: [Slice annot], expr_annot :: annot }
| CondExpr
{ ce_true_branch :: Expr annot
, ce_condition :: Expr annot
, ce_false_branch :: Expr annot
, expr_annot :: annot
}
| BinaryOp { operator :: Op annot, left_op_arg :: Expr annot, right_op_arg :: Expr annot, expr_annot :: annot }
| UnaryOp { operator :: Op annot, op_arg :: Expr annot, expr_annot :: annot }
| Dot { dot_expr :: Expr annot, dot_attribute :: Ident annot, expr_annot :: annot }
| Lambda { lambda_args :: [Parameter annot], lambda_body :: Expr annot, expr_annot :: annot }
| Tuple { tuple_exprs :: [Expr annot], expr_annot :: annot }
| Yield
{ yield_arg :: Maybe (YieldArg annot)
, expr_annot :: annot
}
| Generator { gen_comprehension :: Comprehension annot, expr_annot :: annot }
| Await { await_expr :: Expr annot, expr_annot :: annot }
| ListComp { list_comprehension :: Comprehension annot, expr_annot :: annot }
| List { list_exprs :: [Expr annot], expr_annot :: annot }
| Dictionary { dict_mappings :: [DictKeyDatumList annot], expr_annot :: annot }
| DictComp { dict_comprehension :: Comprehension annot, expr_annot :: annot }
| Set { set_exprs :: [Expr annot], expr_annot :: annot }
| SetComp { set_comprehension :: Comprehension annot, expr_annot :: annot }
| Starred { starred_expr :: Expr annot, expr_annot :: annot }
| Paren { paren_expr :: Expr annot, expr_annot :: annot }
| StringConversion { backquoted_expr :: Expr annot, expr_anot :: annot }
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type ExprSpan = Expr SrcSpan
instance Span ExprSpan where
getSpan = annot
data YieldArg annot
= YieldFrom (Expr annot) annot
| YieldExpr (Expr annot)
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type YieldArgSpan = YieldArg SrcSpan
instance Span YieldArgSpan where
getSpan (YieldFrom _e span) = span
getSpan (YieldExpr e) = getSpan e
instance Annotated Expr where
annot = expr_annot
data DictKeyDatumList annot =
DictMappingPair (Expr annot) (Expr annot)
| DictUnpacking (Expr annot)
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type DictKeyDatumListSpan = DictKeyDatumList SrcSpan
instance Span DictKeyDatumListSpan where
getSpan (DictMappingPair e1 e2) = spanning e1 e2
getSpan (DictUnpacking e) = getSpan e
data Slice annot
= SliceProper
{ slice_lower :: Maybe (Expr annot)
, slice_upper :: Maybe (Expr annot)
, slice_stride :: Maybe (Maybe (Expr annot))
, slice_annot :: annot
}
| SliceExpr
{ slice_expr :: Expr annot
, slice_annot :: annot
}
| SliceEllipsis { slice_annot :: annot }
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type SliceSpan = Slice SrcSpan
instance Span SliceSpan where
getSpan = annot
instance Annotated Slice where
annot = slice_annot
data Op annot
= And { op_annot :: annot }
| Or { op_annot :: annot }
| Not { op_annot :: annot }
| Exponent { op_annot :: annot }
| LessThan { op_annot :: annot }
| GreaterThan { op_annot :: annot }
| Equality { op_annot :: annot }
| GreaterThanEquals { op_annot :: annot }
| LessThanEquals { op_annot :: annot }
| NotEquals { op_annot :: annot }
| NotEqualsV2 { op_annot :: annot }
| In { op_annot :: annot }
| Is { op_annot :: annot }
| IsNot { op_annot :: annot }
| NotIn { op_annot :: annot }
| BinaryOr { op_annot :: annot }
| Xor { op_annot :: annot }
| BinaryAnd { op_annot :: annot }
| ShiftLeft { op_annot :: annot }
| ShiftRight { op_annot :: annot }
| Multiply { op_annot :: annot }
| Plus { op_annot :: annot }
| Minus { op_annot :: annot }
| Divide { op_annot :: annot }
| FloorDivide { op_annot :: annot }
| MatrixMult { op_annot :: annot }
| Invert { op_annot :: annot }
| Modulo { op_annot :: annot }
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type OpSpan = Op SrcSpan
instance Span OpSpan where
getSpan = annot
instance Annotated Op where
annot = op_annot
data AssignOp annot
= PlusAssign { assignOp_annot :: annot }
| MinusAssign { assignOp_annot :: annot }
| MultAssign { assignOp_annot :: annot }
| DivAssign { assignOp_annot :: annot }
| ModAssign { assignOp_annot :: annot }
| PowAssign { assignOp_annot :: annot }
| BinAndAssign { assignOp_annot :: annot }
| BinOrAssign { assignOp_annot :: annot }
| BinXorAssign { assignOp_annot :: annot }
| LeftShiftAssign { assignOp_annot :: annot }
| RightShiftAssign { assignOp_annot :: annot }
| FloorDivAssign { assignOp_annot :: annot }
| MatrixMultAssign { assignOp_annot :: annot }
deriving (Eq,Ord,Show,Typeable,Data,Functor)
type AssignOpSpan = AssignOp SrcSpan
instance Span AssignOpSpan where
getSpan = annot
instance Annotated AssignOp where
annot = assignOp_annot