hpython-0.1: Python language tools

Copyright(C) CSIRO 2017-2018
LicenseBSD3
MaintainerIsaac Elliott <isaace71295@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Language.Python.Syntax.Expr

Contents

Description

 
Synopsis

Expressions

data Expr (v :: [*]) a Source #

This large sum type covers all valid Python expressions

Constructors

Unit
()

https://docs.python.org/3/reference/expressions.html#parenthesized-forms

Lambda
lambda x, y: x

https://docs.python.org/3/reference/expressions.html#lambda

Yield
yield
yield a
yield a, b

https://docs.python.org/3/reference/expressions.html#yield-expressions

YieldFrom
yield from a

https://docs.python.org/3/reference/expressions.html#yield-expressions

Ternary
a if b else c

https://docs.python.org/3/reference/expressions.html#conditional-expressions

ListComp
[a for b in c if d]

https://docs.python.org/3/reference/expressions.html#list-displays

List
[a, b, c]

https://docs.python.org/3/reference/expressions.html#list-displays

DictComp
{a: b for c in d if e}

https://docs.python.org/3/reference/expressions.html#dictionary-displays

Dict
{}
{a: 1, b: 2, c: 3}

https://docs.python.org/3/reference/expressions.html#dictionary-displays

SetComp
{a for b in c if d}

https://docs.python.org/3/reference/expressions.html#set-displays

Set
{a, b, c}

https://docs.python.org/3/reference/expressions.html#set-displays

Deref
a.b

https://docs.python.org/3/reference/expressions.html#attribute-references

Subscript
a[b]
a[:]
a[:, b:]

etc.

https://docs.python.org/3/reference/expressions.html#subscriptions

Call
f(x)

https://docs.python.org/3/reference/expressions.html#calls

None
None

https://docs.python.org/3/library/constants.html#None

Ellipsis
...

https://docs.python.org/3/library/constants.html#Ellipsis

BinOp
a + b

https://docs.python.org/3/reference/expressions.html#the-power-operator

https://docs.python.org/3/reference/expressions.html#binary-arithmetic-operations

https://docs.python.org/3/reference/expressions.html#shifting-operations

https://docs.python.org/3/reference/expressions.html#binary-bitwise-operations

https://docs.python.org/3/reference/expressions.html#comparisons

https://docs.python.org/3/reference/expressions.html#membership-test-operations

https://docs.python.org/3/reference/expressions.html#is-not

https://docs.python.org/3/reference/expressions.html#boolean-operations

UnOp
-a
~a
+a

https://docs.python.org/3/reference/expressions.html#unary-arithmetic-and-bitwise-operations

Parens 
Ident
a

https://docs.python.org/3/reference/expressions.html#atom-identifiers

Fields

Int
1

@0xF3A

@0o177

0b1011

https://docs.python.org/3/reference/lexical_analysis.html#grammar-token-integer

Float
1.
3.14
10e100

https://docs.python.org/3/reference/lexical_analysis.html#floating-point-literals

Imag
10j
5.j

https://docs.python.org/3/reference/lexical_analysis.html#floating-point-literals

Bool
True
False

https://docs.python.org/3/library/constants.html#True

https://docs.python.org/3/library/constants.html#False

String
"asdf"
b"asdf"
"asdf" 'asdf'
'''asdf'''

https://docs.python.org/3/reference/lexical_analysis.html#grammar-token-stringliteral

Tuple
a, b, c
(a, b)
(a,)

https://docs.python.org/3/reference/expressions.html#expression-lists

Not
not a

https://docs.python.org/3/reference/expressions.html#boolean-operations

Generator
(a for b in c)

https://docs.python.org/3/reference/expressions.html#generator-expressions

Await
await a

https://docs.python.org/3/reference/expressions.html#await

Instances
Validated Expr Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

unvalidated :: Getter (Expr v a) (Expr [] a) Source #

HasExprs Expr Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

_Exprs :: Traversal (Expr v a) (Expr [] a) (Expr v a) (Expr [] a) Source #

AsTupleItem Expr Source # 
Instance details

Defined in Language.Python.DSL

AsWithItem Expr Source # 
Instance details

Defined in Language.Python.DSL

AsExceptAs Expr Source # 
Instance details

Defined in Language.Python.DSL

AsSetItem Expr Source # 
Instance details

Defined in Language.Python.DSL

Methods

si_ :: Raw Expr -> Raw SetItem Source #

AsListItem Expr Source # 
Instance details

Defined in Language.Python.DSL

Methods

li_ :: Raw Expr -> Raw ListItem Source #

AsLine Expr Source # 
Instance details

Defined in Language.Python.DSL

Methods

line_ :: Raw Expr -> Raw Line Source #

DoubleStarSyntax Expr DictItem Source #

See dict_

Instance details

Defined in Language.Python.DSL

Methods

ss_ :: Raw Expr -> Raw DictItem Source #

DoubleStarSyntax Expr Arg Source #

See call_

Instance details

Defined in Language.Python.DSL

Methods

ss_ :: Raw Expr -> Raw Arg Source #

StarSyntax Expr TupleItem Source #

See tuple_

Instance details

Defined in Language.Python.DSL

Methods

s_ :: Raw Expr -> Raw TupleItem Source #

StarSyntax Expr SetItem Source #

See set_

Instance details

Defined in Language.Python.DSL

Methods

s_ :: Raw Expr -> Raw SetItem Source #

StarSyntax Expr ListItem Source #

See list_

Instance details

Defined in Language.Python.DSL

Methods

s_ :: Raw Expr -> Raw ListItem Source #

StarSyntax Expr Arg Source #

See call_

Instance details

Defined in Language.Python.DSL

Methods

s_ :: Raw Expr -> Raw Arg Source #

PositionalSyntax Arg Expr Source #

See call_

Instance details

Defined in Language.Python.DSL

Methods

p_ :: Raw Expr -> Raw Arg Source #

ColonSyntax Expr DictItem Source #

Constructing dictionary items

(.:) :: Raw SimpleStatement -> Raw SimpleStatement -> Raw DictItem
Instance details

Defined in Language.Python.DSL

Methods

(.:) :: Raw Expr -> Raw Expr -> Raw DictItem Source #

As Expr Ident ExceptAs Source #

See exceptAs_

Instance details

Defined in Language.Python.DSL

Methods

as_ :: Raw Expr -> Raw Ident -> Raw ExceptAs Source #

As Expr Expr WithItem Source #

See with_

Instance details

Defined in Language.Python.DSL

Methods

as_ :: Raw Expr -> Raw Expr -> Raw WithItem Source #

InSyntax Expr (Raw Expr) Source #
>>> var_ "a" `in_` var_ "b"
a in b
Instance details

Defined in Language.Python.DSL

Methods

in_ :: Raw Expr -> Raw Expr -> Raw Expr Source #

Functor (Expr v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

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

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

Foldable (Expr v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fold :: Monoid m => Expr v m -> m #

foldMap :: Monoid m => (a -> m) -> Expr v a -> m #

foldr :: (a -> b -> b) -> b -> Expr v a -> b #

foldr' :: (a -> b -> b) -> b -> Expr v a -> b #

foldl :: (b -> a -> b) -> b -> Expr v a -> b #

foldl' :: (b -> a -> b) -> b -> Expr v a -> b #

foldr1 :: (a -> a -> a) -> Expr v a -> a #

foldl1 :: (a -> a -> a) -> Expr v a -> a #

toList :: Expr v a -> [a] #

null :: Expr v a -> Bool #

length :: Expr v a -> Int #

elem :: Eq a => a -> Expr v a -> Bool #

maximum :: Ord a => Expr v a -> a #

minimum :: Ord a => Expr v a -> a #

sum :: Num a => Expr v a -> a #

product :: Num a => Expr v a -> a #

Traversable (Expr v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

traverse :: Applicative f => (a -> f b) -> Expr v a -> f (Expr v b) #

sequenceA :: Applicative f => Expr v (f a) -> f (Expr v a) #

mapM :: Monad m => (a -> m b) -> Expr v a -> m (Expr v b) #

sequence :: Monad m => Expr v (m a) -> m (Expr v a) #

Eq a => Eq (Expr v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

(==) :: Expr v a -> Expr v a -> Bool #

(/=) :: Expr v a -> Expr v a -> Bool #

Num (Expr ([] :: [Type]) ()) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

(+) :: Expr [] () -> Expr [] () -> Expr [] () #

(-) :: Expr [] () -> Expr [] () -> Expr [] () #

(*) :: Expr [] () -> Expr [] () -> Expr [] () #

negate :: Expr [] () -> Expr [] () #

abs :: Expr [] () -> Expr [] () #

signum :: Expr [] () -> Expr [] () #

fromInteger :: Integer -> Expr [] () #

Show a => Show (Expr v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

showsPrec :: Int -> Expr v a -> ShowS #

show :: Expr v a -> String #

showList :: [Expr v a] -> ShowS #

IsString (Expr ([] :: [Type]) ()) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fromString :: String -> Expr [] () #

Generic (Expr v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Associated Types

type Rep (Expr v a) :: Type -> Type #

Methods

from :: Expr v a -> Rep (Expr v a) x #

to :: Rep (Expr v a) x -> Expr v a #

Plated (Expr ([] :: [Type]) a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

plate :: Traversal' (Expr [] a) (Expr [] a) #

HasTrailingWhitespace (Expr v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

HasNewlines (Expr v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

type Rep (Expr v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

type Rep (Expr v a) = D1 (MetaData "Expr" "Language.Python.Syntax.Expr" "hpython-0.1-AGWlxbmKlB6B0gKumFrQ3a" False) ((((C1 (MetaCons "Unit" PrefixI True) (S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "_unsafeUnitWhitespaceInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]) :*: S1 (MetaSel (Just "_unsafeUnitWhitespaceRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]))) :+: (C1 (MetaCons "Lambda" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeLambdaWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :*: (S1 (MetaSel (Just "_unsafeLambdaArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CommaSep (Param v a))) :*: (S1 (MetaSel (Just "_unsafeLambdaColon") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Colon) :*: S1 (MetaSel (Just "_unsafeLambdaBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a))))) :+: C1 (MetaCons "Yield" PrefixI True) (S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "_unsafeYieldWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]) :*: S1 (MetaSel (Just "_unsafeYieldValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CommaSep (Expr v a))))))) :+: ((C1 (MetaCons "YieldFrom" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeYieldWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :*: (S1 (MetaSel (Just "_unsafeFromWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]) :*: S1 (MetaSel (Just "_unsafeYieldFromValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a)))) :+: C1 (MetaCons "Ternary" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "_unsafeTernaryValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a)) :*: S1 (MetaSel (Just "_unsafeTernaryWhitespaceIf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]))) :*: (S1 (MetaSel (Just "_unsafeTernaryCond") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a)) :*: (S1 (MetaSel (Just "_unsafeTernaryWhitespaceElse") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]) :*: S1 (MetaSel (Just "_unsafeTernaryElse") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a)))))) :+: (C1 (MetaCons "ListComp" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeListCompWhitespaceLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :*: (S1 (MetaSel (Just "_unsafeListCompValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Comprehension Expr v a)) :*: S1 (MetaSel (Just "_unsafeListCompWhitespaceRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]))) :+: C1 (MetaCons "List" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeListWhitespaceLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :*: (S1 (MetaSel (Just "_unsafeListValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (CommaSep1' (ListItem v a)))) :*: S1 (MetaSel (Just "_unsafeListWhitespaceRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])))))) :+: ((C1 (MetaCons "DictComp" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeDictCompWhitespaceLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :*: (S1 (MetaSel (Just "_unsafeDictCompValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Comprehension DictItem v a)) :*: S1 (MetaSel (Just "_unsafeDictCompWhitespaceRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]))) :+: (C1 (MetaCons "Dict" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeDictWhitespaceLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :*: (S1 (MetaSel (Just "_unsafeDictValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (CommaSep1' (DictItem v a)))) :*: S1 (MetaSel (Just "_unsafeDictWhitespaceRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]))) :+: C1 (MetaCons "SetComp" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeSetCompWhitespaceLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :*: (S1 (MetaSel (Just "_unsafeSetCompValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Comprehension SetItem v a)) :*: S1 (MetaSel (Just "_unsafeSetCompWhitespaceRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]))))) :+: ((C1 (MetaCons "Set" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeSetWhitespaceLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :*: (S1 (MetaSel (Just "_unsafeSetValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CommaSep1' (SetItem v a))) :*: S1 (MetaSel (Just "_unsafeSetWhitespaceRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]))) :+: C1 (MetaCons "Deref" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeDerefValueLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a))) :*: (S1 (MetaSel (Just "_unsafeDerefWhitespaceLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]) :*: S1 (MetaSel (Just "_unsafeDerefValueRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ident v a))))) :+: (C1 (MetaCons "Subscript" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeSubscriptValueLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a))) :*: (S1 (MetaSel (Just "_unsafeSubscriptWhitespaceLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]) :*: (S1 (MetaSel (Just "_unsafeSubscriptValueRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CommaSep1' (Subscript v a))) :*: S1 (MetaSel (Just "_unsafeSubscriptWhitespaceRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])))) :+: C1 (MetaCons "Call" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeCallFunction") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a))) :*: (S1 (MetaSel (Just "_unsafeCallWhitespaceLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]) :*: (S1 (MetaSel (Just "_unsafeCallArguments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (CommaSep1' (Arg v a)))) :*: S1 (MetaSel (Just "_unsafeCallWhitespaceRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])))))))) :+: (((C1 (MetaCons "None" PrefixI True) (S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeNoneWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :+: (C1 (MetaCons "Ellipsis" PrefixI True) (S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeEllipsisWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :+: C1 (MetaCons "BinOp" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeBinOpExprLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a))) :*: (S1 (MetaSel (Just "_unsafeBinOpOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (BinOp a)) :*: S1 (MetaSel (Just "_unsafeBinOpExprRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a)))))) :+: ((C1 (MetaCons "UnOp" PrefixI True) (S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "_unsafeUnOpOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (UnOp a)) :*: S1 (MetaSel (Just "_unsafeUnOpValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a)))) :+: C1 (MetaCons "Parens" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeParensWhitespaceLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :*: (S1 (MetaSel (Just "_unsafeParensValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a)) :*: S1 (MetaSel (Just "_unsafeParensWhitespaceAfter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])))) :+: (C1 (MetaCons "Ident" PrefixI True) (S1 (MetaSel (Just "_unsafeIdentValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ident v a))) :+: C1 (MetaCons "Int" PrefixI True) (S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "_unsafeIntValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IntLiteral a)) :*: S1 (MetaSel (Just "_unsafeIntWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])))))) :+: (((C1 (MetaCons "Float" PrefixI True) (S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "_unsafeFloatValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (FloatLiteral a)) :*: S1 (MetaSel (Just "_unsafeFloatWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]))) :+: C1 (MetaCons "Imag" PrefixI True) (S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "_unsafeImagValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ImagLiteral a)) :*: S1 (MetaSel (Just "_unsafeImagWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])))) :+: (C1 (MetaCons "Bool" PrefixI True) (S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "_unsafeBoolValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "_unsafeBoolWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]))) :+: C1 (MetaCons "String" PrefixI True) (S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeStringValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (StringLiteral a)))))) :+: ((C1 (MetaCons "Tuple" PrefixI True) ((S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_unsafeTupleHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (TupleItem v a))) :*: (S1 (MetaSel (Just "_unsafeTupleWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Comma) :*: S1 (MetaSel (Just "_unsafeTupleTail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (CommaSep1' (TupleItem v a)))))) :+: C1 (MetaCons "Not" PrefixI True) (S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "_unsafeNotWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]) :*: S1 (MetaSel (Just "_unsafeNotValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a))))) :+: (C1 (MetaCons "Generator" PrefixI True) (S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "_generatorValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Comprehension Expr v a))) :+: C1 (MetaCons "Await" PrefixI True) (S1 (MetaSel (Just "_unsafeExprAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "_unsafeAwaitWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]) :*: S1 (MetaSel (Just "_unsafeAwaitValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a)))))))))

class HasExprs s where Source #

Traversal over all the expressions in a term

Methods

_Exprs :: Traversal (s v a) (s '[] a) (Expr v a) (Expr '[] a) Source #

Instances
HasExprs Expr Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

_Exprs :: Traversal (Expr v a) (Expr [] a) (Expr v a) (Expr [] a) Source #

HasExprs TupleItem Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

_Exprs :: Traversal (TupleItem v a) (TupleItem [] a) (Expr v a) (Expr [] a) Source #

HasExprs SetItem Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

_Exprs :: Traversal (SetItem v a) (SetItem [] a) (Expr v a) (Expr [] a) Source #

HasExprs ListItem Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

_Exprs :: Traversal (ListItem v a) (ListItem [] a) (Expr v a) (Expr [] a) Source #

HasExprs Arg Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

_Exprs :: Traversal (Arg v a) (Arg [] a) (Expr v a) (Expr [] a) Source #

HasExprs Param Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

_Exprs :: Traversal (Param v a) (Param [] a) (Expr v a) (Expr [] a) Source #

HasExprs CompoundStatement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Exprs :: Traversal (CompoundStatement v a) (CompoundStatement [] a) (Expr v a) (Expr [] a) Source #

HasExprs Decorator Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Exprs :: Traversal (Decorator v a) (Decorator [] a) (Expr v a) (Expr [] a) Source #

HasExprs WithItem Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Exprs :: Traversal (WithItem v a) (WithItem [] a) (Expr v a) (Expr [] a) Source #

HasExprs Suite Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Exprs :: Traversal (Suite v a) (Suite [] a) (Expr v a) (Expr [] a) Source #

HasExprs ExceptAs Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Exprs :: Traversal (ExceptAs v a) (ExceptAs [] a) (Expr v a) (Expr [] a) Source #

HasExprs SimpleStatement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Exprs :: Traversal (SimpleStatement v a) (SimpleStatement [] a) (Expr v a) (Expr [] a) Source #

HasExprs Statement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Exprs :: Traversal (Statement v a) (Statement [] a) (Expr v a) (Expr [] a) Source #

HasExprs SmallStatement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Exprs :: Traversal (SmallStatement v a) (SmallStatement [] a) (Expr v a) (Expr [] a) Source #

HasExprs Block Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Exprs :: Traversal (Block v a) (Block [] a) (Expr v a) (Expr [] a) Source #

HasExprs Line Source # 
Instance details

Defined in Language.Python.DSL

Methods

_Exprs :: Traversal (Line v a) (Line [] a) (Expr v a) (Expr [] a) Source #

exprAnn :: Lens' (Expr v a) a Source #

Lens on the top-level annotation in an expression

shouldGroupLeft :: BinOp a -> Expr v a -> Bool Source #

shouldGroupLeft op left returns true if left needs to be parenthesised when it is the left argument of op

shouldGroupRight :: BinOp a -> Expr v a -> Bool Source #

shouldGroupRight op right returns true if right needs to be parenthesised when it is the right argument of op

Parameters and arguments

data Param (v :: [*]) a Source #

Instances
Validated Param Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

unvalidated :: Getter (Param v a) (Param [] a) Source #

HasExprs Param Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

_Exprs :: Traversal (Param v a) (Param [] a) (Expr v a) (Expr [] a) Source #

KeywordSyntax Param Source #

See def_

Instance details

Defined in Language.Python.DSL

Methods

k_ :: Raw Ident -> Raw Expr -> Raw Param Source #

DoubleStarSyntax Ident Param Source #

See def_

Instance details

Defined in Language.Python.DSL

Methods

ss_ :: Raw Ident -> Raw Param Source #

StarSyntax Ident Param Source #

See def_

Instance details

Defined in Language.Python.DSL

Methods

s_ :: Raw Ident -> Raw Param Source #

PositionalSyntax Param Ident Source #

See def_

Instance details

Defined in Language.Python.DSL

Methods

p_ :: Raw Ident -> Raw Param Source #

ColonSyntax Param Param Source #

Function parameter type annotations

(.:) :: Raw Param -> Raw SimpleStatement -> Raw Param

star_ can be annotated using .:, but it will have no effect on the output program, as unnamed starred parameters cannot have type annotations.

See def_

Instance details

Defined in Language.Python.DSL

Methods

(.:) :: Raw Param -> Raw Expr -> Raw Param Source #

Functor (Param v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fmap :: (a -> b) -> Param v a -> Param v b #

(<$) :: a -> Param v b -> Param v a #

Foldable (Param v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fold :: Monoid m => Param v m -> m #

foldMap :: Monoid m => (a -> m) -> Param v a -> m #

foldr :: (a -> b -> b) -> b -> Param v a -> b #

foldr' :: (a -> b -> b) -> b -> Param v a -> b #

foldl :: (b -> a -> b) -> b -> Param v a -> b #

foldl' :: (b -> a -> b) -> b -> Param v a -> b #

foldr1 :: (a -> a -> a) -> Param v a -> a #

foldl1 :: (a -> a -> a) -> Param v a -> a #

toList :: Param v a -> [a] #

null :: Param v a -> Bool #

length :: Param v a -> Int #

elem :: Eq a => a -> Param v a -> Bool #

maximum :: Ord a => Param v a -> a #

minimum :: Ord a => Param v a -> a #

sum :: Num a => Param v a -> a #

product :: Num a => Param v a -> a #

Traversable (Param v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

traverse :: Applicative f => (a -> f b) -> Param v a -> f (Param v b) #

sequenceA :: Applicative f => Param v (f a) -> f (Param v a) #

mapM :: Monad m => (a -> m b) -> Param v a -> m (Param v b) #

sequence :: Monad m => Param v (m a) -> m (Param v a) #

Eq a => Eq (Param v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

(==) :: Param v a -> Param v a -> Bool #

(/=) :: Param v a -> Param v a -> Bool #

Show a => Show (Param v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

showsPrec :: Int -> Param v a -> ShowS #

show :: Param v a -> String #

showList :: [Param v a] -> ShowS #

IsString (Param ([] :: [Type]) ()) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fromString :: String -> Param [] () #

HasTrailingWhitespace (Param v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

HasNewlines (Param v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

paramAnn :: Lens' (Param v a) a Source #

Lens on the syntrax tree annotation on a parameter

paramType_ :: Functor f => (Maybe (Colon, Expr v a) -> f (Maybe (Colon, Expr '[] a))) -> Param v a -> f (Param '[] a) Source #

A faux-lens on the optional Python type annotation which may follow a parameter

This is not a lawful Lens because setting an UnnamedStarParam's type won't have any effect.

This optic, like many others in hpython, loses validation information (the v type parameter)

The following is an example, where int is the paramtype:

def foo(x: int):

paramType :: Traversal (Param v a) (Param '[] a) (Colon, Expr v a) (Colon, Expr '[] a) Source #

Traversal targeting the Python type annotations which may follow a parameter

paramName :: Traversal (Param v a) (Param '[] a) (Ident v a) (Ident '[] a) Source #

(affine) Traversal on the name of a parameter

The name is x in the following examples:

def foo(x):
def foo(x=None):
def foo(*x):
def foo(**x):

But the following example does not have a paramName:

def foo(*):

data Arg (v :: [*]) a Source #

Actual parameters for functions

In the following examples, x is an actual parameter.

y = foo(x)
y = bar(quux=x)
y = baz(*x)
y = flux(**x)
Instances
Validated Arg Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

unvalidated :: Getter (Arg v a) (Arg [] a) Source #

HasExprs Arg Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

_Exprs :: Traversal (Arg v a) (Arg [] a) (Expr v a) (Expr [] a) Source #

KeywordSyntax Arg Source #

See call_

Instance details

Defined in Language.Python.DSL

Methods

k_ :: Raw Ident -> Raw Expr -> Raw Arg Source #

DoubleStarSyntax Expr Arg Source #

See call_

Instance details

Defined in Language.Python.DSL

Methods

ss_ :: Raw Expr -> Raw Arg Source #

StarSyntax Expr Arg Source #

See call_

Instance details

Defined in Language.Python.DSL

Methods

s_ :: Raw Expr -> Raw Arg Source #

PositionalSyntax Arg Expr Source #

See call_

Instance details

Defined in Language.Python.DSL

Methods

p_ :: Raw Expr -> Raw Arg Source #

Functor (Arg v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fmap :: (a -> b) -> Arg v a -> Arg v b #

(<$) :: a -> Arg v b -> Arg v a #

Foldable (Arg v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fold :: Monoid m => Arg v m -> m #

foldMap :: Monoid m => (a -> m) -> Arg v a -> m #

foldr :: (a -> b -> b) -> b -> Arg v a -> b #

foldr' :: (a -> b -> b) -> b -> Arg v a -> b #

foldl :: (b -> a -> b) -> b -> Arg v a -> b #

foldl' :: (b -> a -> b) -> b -> Arg v a -> b #

foldr1 :: (a -> a -> a) -> Arg v a -> a #

foldl1 :: (a -> a -> a) -> Arg v a -> a #

toList :: Arg v a -> [a] #

null :: Arg v a -> Bool #

length :: Arg v a -> Int #

elem :: Eq a => a -> Arg v a -> Bool #

maximum :: Ord a => Arg v a -> a #

minimum :: Ord a => Arg v a -> a #

sum :: Num a => Arg v a -> a #

product :: Num a => Arg v a -> a #

Traversable (Arg v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

traverse :: Applicative f => (a -> f b) -> Arg v a -> f (Arg v b) #

sequenceA :: Applicative f => Arg v (f a) -> f (Arg v a) #

mapM :: Monad m => (a -> m b) -> Arg v a -> m (Arg v b) #

sequence :: Monad m => Arg v (m a) -> m (Arg v a) #

Eq a => Eq (Arg v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

(==) :: Arg v a -> Arg v a -> Bool #

(/=) :: Arg v a -> Arg v a -> Bool #

Show a => Show (Arg v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

showsPrec :: Int -> Arg v a -> ShowS #

show :: Arg v a -> String #

showList :: [Arg v a] -> ShowS #

IsString (Arg ([] :: [Type]) ()) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fromString :: String -> Arg [] () #

HasNewlines (Arg v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

argExpr :: Lens (Arg v a) (Arg '[] a) (Expr v a) (Expr '[] a) Source #

Lens on the Python expression which is passed as the argument

Comprehension expressions

data Comprehension e (v :: [*]) a Source #

A Python for comprehension, such as

x for y in z

Constructors

Comprehension a (e v a) (CompFor v a) [Either (CompFor v a) (CompIf v a)]

expr comp_for (comp_for | comp_if)*

Instances
Functor (e v) => Functor (Comprehension e v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

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

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

Foldable (e v) => Foldable (Comprehension e v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fold :: Monoid m => Comprehension e v m -> m #

foldMap :: Monoid m => (a -> m) -> Comprehension e v a -> m #

foldr :: (a -> b -> b) -> b -> Comprehension e v a -> b #

foldr' :: (a -> b -> b) -> b -> Comprehension e v a -> b #

foldl :: (b -> a -> b) -> b -> Comprehension e v a -> b #

foldl' :: (b -> a -> b) -> b -> Comprehension e v a -> b #

foldr1 :: (a -> a -> a) -> Comprehension e v a -> a #

foldl1 :: (a -> a -> a) -> Comprehension e v a -> a #

toList :: Comprehension e v a -> [a] #

null :: Comprehension e v a -> Bool #

length :: Comprehension e v a -> Int #

elem :: Eq a => a -> Comprehension e v a -> Bool #

maximum :: Ord a => Comprehension e v a -> a #

minimum :: Ord a => Comprehension e v a -> a #

sum :: Num a => Comprehension e v a -> a #

product :: Num a => Comprehension e v a -> a #

Traversable (e v) => Traversable (Comprehension e v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

traverse :: Applicative f => (a -> f b) -> Comprehension e v a -> f (Comprehension e v b) #

sequenceA :: Applicative f => Comprehension e v (f a) -> f (Comprehension e v a) #

mapM :: Monad m => (a -> m b) -> Comprehension e v a -> m (Comprehension e v b) #

sequence :: Monad m => Comprehension e v (m a) -> m (Comprehension e v a) #

(Eq a, Eq (e v a)) => Eq (Comprehension e v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

(==) :: Comprehension e v a -> Comprehension e v a -> Bool #

(/=) :: Comprehension e v a -> Comprehension e v a -> Bool #

(Show a, Show (e v a)) => Show (Comprehension e v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

showsPrec :: Int -> Comprehension e v a -> ShowS #

show :: Comprehension e v a -> String #

showList :: [Comprehension e v a] -> ShowS #

HasTrailingWhitespace (Comprehension e v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

HasNewlines (e v a) => HasNewlines (Comprehension e v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

data CompIf (v :: [*]) a Source #

A condition inside a comprehension, e.g. [x for x in xs if even(x)]

Constructors

CompIf a [Whitespace] (Expr v a) 
Instances
Functor (CompIf v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

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

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

Foldable (CompIf v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fold :: Monoid m => CompIf v m -> m #

foldMap :: Monoid m => (a -> m) -> CompIf v a -> m #

foldr :: (a -> b -> b) -> b -> CompIf v a -> b #

foldr' :: (a -> b -> b) -> b -> CompIf v a -> b #

foldl :: (b -> a -> b) -> b -> CompIf v a -> b #

foldl' :: (b -> a -> b) -> b -> CompIf v a -> b #

foldr1 :: (a -> a -> a) -> CompIf v a -> a #

foldl1 :: (a -> a -> a) -> CompIf v a -> a #

toList :: CompIf v a -> [a] #

null :: CompIf v a -> Bool #

length :: CompIf v a -> Int #

elem :: Eq a => a -> CompIf v a -> Bool #

maximum :: Ord a => CompIf v a -> a #

minimum :: Ord a => CompIf v a -> a #

sum :: Num a => CompIf v a -> a #

product :: Num a => CompIf v a -> a #

Traversable (CompIf v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

traverse :: Applicative f => (a -> f b) -> CompIf v a -> f (CompIf v b) #

sequenceA :: Applicative f => CompIf v (f a) -> f (CompIf v a) #

mapM :: Monad m => (a -> m b) -> CompIf v a -> m (CompIf v b) #

sequence :: Monad m => CompIf v (m a) -> m (CompIf v a) #

Eq a => Eq (CompIf v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

(==) :: CompIf v a -> CompIf v a -> Bool #

(/=) :: CompIf v a -> CompIf v a -> Bool #

Show a => Show (CompIf v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

showsPrec :: Int -> CompIf v a -> ShowS #

show :: CompIf v a -> String #

showList :: [CompIf v a] -> ShowS #

HasTrailingWhitespace (CompIf v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

HasNewlines (CompIf v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

data CompFor (v :: [*]) a Source #

A nested comprehesion, e.g. [(x, y) for x in xs for y in ys]

Constructors

CompFor a [Whitespace] (Expr v a) [Whitespace] (Expr v a) 
Instances
Functor (CompFor v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

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

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

Foldable (CompFor v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fold :: Monoid m => CompFor v m -> m #

foldMap :: Monoid m => (a -> m) -> CompFor v a -> m #

foldr :: (a -> b -> b) -> b -> CompFor v a -> b #

foldr' :: (a -> b -> b) -> b -> CompFor v a -> b #

foldl :: (b -> a -> b) -> b -> CompFor v a -> b #

foldl' :: (b -> a -> b) -> b -> CompFor v a -> b #

foldr1 :: (a -> a -> a) -> CompFor v a -> a #

foldl1 :: (a -> a -> a) -> CompFor v a -> a #

toList :: CompFor v a -> [a] #

null :: CompFor v a -> Bool #

length :: CompFor v a -> Int #

elem :: Eq a => a -> CompFor v a -> Bool #

maximum :: Ord a => CompFor v a -> a #

minimum :: Ord a => CompFor v a -> a #

sum :: Num a => CompFor v a -> a #

product :: Num a => CompFor v a -> a #

Traversable (CompFor v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

traverse :: Applicative f => (a -> f b) -> CompFor v a -> f (CompFor v b) #

sequenceA :: Applicative f => CompFor v (f a) -> f (CompFor v a) #

mapM :: Monad m => (a -> m b) -> CompFor v a -> m (CompFor v b) #

sequence :: Monad m => CompFor v (m a) -> m (CompFor v a) #

ForSyntax (Raw CompFor) In Source #
for_ :: Raw In -> Raw CompFor
>>> comp_ (var_ "a") (for_ $ var_ "a" `in_` var_ "b") []
a for a in b
Instance details

Defined in Language.Python.DSL

Methods

for_ :: Raw In -> Raw CompFor Source #

Eq a => Eq (CompFor v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

(==) :: CompFor v a -> CompFor v a -> Bool #

(/=) :: CompFor v a -> CompFor v a -> Bool #

Show a => Show (CompFor v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

showsPrec :: Int -> CompFor v a -> ShowS #

show :: CompFor v a -> String #

showList :: [CompFor v a] -> ShowS #

HasTrailingWhitespace (CompFor v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

HasNewlines (CompFor v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Collection items

data DictItem (v :: [*]) a Source #

a : b or **a

Used to construct dictionaries, e.g. { 1: a, 2: b, **c }

https://docs.python.org/3/reference/expressions.html#dictionary-displays

Instances
Validated DictItem Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

unvalidated :: Getter (DictItem v a) (DictItem [] a) Source #

DoubleStarSyntax Expr DictItem Source #

See dict_

Instance details

Defined in Language.Python.DSL

Methods

ss_ :: Raw Expr -> Raw DictItem Source #

ColonSyntax Expr DictItem Source #

Constructing dictionary items

(.:) :: Raw SimpleStatement -> Raw SimpleStatement -> Raw DictItem
Instance details

Defined in Language.Python.DSL

Methods

(.:) :: Raw Expr -> Raw Expr -> Raw DictItem Source #

Functor (DictItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fmap :: (a -> b) -> DictItem v a -> DictItem v b #

(<$) :: a -> DictItem v b -> DictItem v a #

Foldable (DictItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fold :: Monoid m => DictItem v m -> m #

foldMap :: Monoid m => (a -> m) -> DictItem v a -> m #

foldr :: (a -> b -> b) -> b -> DictItem v a -> b #

foldr' :: (a -> b -> b) -> b -> DictItem v a -> b #

foldl :: (b -> a -> b) -> b -> DictItem v a -> b #

foldl' :: (b -> a -> b) -> b -> DictItem v a -> b #

foldr1 :: (a -> a -> a) -> DictItem v a -> a #

foldl1 :: (a -> a -> a) -> DictItem v a -> a #

toList :: DictItem v a -> [a] #

null :: DictItem v a -> Bool #

length :: DictItem v a -> Int #

elem :: Eq a => a -> DictItem v a -> Bool #

maximum :: Ord a => DictItem v a -> a #

minimum :: Ord a => DictItem v a -> a #

sum :: Num a => DictItem v a -> a #

product :: Num a => DictItem v a -> a #

Traversable (DictItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

traverse :: Applicative f => (a -> f b) -> DictItem v a -> f (DictItem v b) #

sequenceA :: Applicative f => DictItem v (f a) -> f (DictItem v a) #

mapM :: Monad m => (a -> m b) -> DictItem v a -> m (DictItem v b) #

sequence :: Monad m => DictItem v (m a) -> m (DictItem v a) #

Eq a => Eq (DictItem v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

(==) :: DictItem v a -> DictItem v a -> Bool #

(/=) :: DictItem v a -> DictItem v a -> Bool #

Show a => Show (DictItem v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

showsPrec :: Int -> DictItem v a -> ShowS #

show :: DictItem v a -> String #

showList :: [DictItem v a] -> ShowS #

HasTrailingWhitespace (DictItem v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

HasNewlines (DictItem v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

data ListItem (v :: [*]) a Source #

a or *a

Used to construct lists, e.g. [ 1, x, **c ]

https://docs.python.org/3/reference/expressions.html#list-displays

Instances
Validated ListItem Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

unvalidated :: Getter (ListItem v a) (ListItem [] a) Source #

HasExprs ListItem Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

_Exprs :: Traversal (ListItem v a) (ListItem [] a) (Expr v a) (Expr [] a) Source #

AsListItem ListItem Source # 
Instance details

Defined in Language.Python.DSL

StarSyntax Expr ListItem Source #

See list_

Instance details

Defined in Language.Python.DSL

Methods

s_ :: Raw Expr -> Raw ListItem Source #

Functor (ListItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fmap :: (a -> b) -> ListItem v a -> ListItem v b #

(<$) :: a -> ListItem v b -> ListItem v a #

Foldable (ListItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fold :: Monoid m => ListItem v m -> m #

foldMap :: Monoid m => (a -> m) -> ListItem v a -> m #

foldr :: (a -> b -> b) -> b -> ListItem v a -> b #

foldr' :: (a -> b -> b) -> b -> ListItem v a -> b #

foldl :: (b -> a -> b) -> b -> ListItem v a -> b #

foldl' :: (b -> a -> b) -> b -> ListItem v a -> b #

foldr1 :: (a -> a -> a) -> ListItem v a -> a #

foldl1 :: (a -> a -> a) -> ListItem v a -> a #

toList :: ListItem v a -> [a] #

null :: ListItem v a -> Bool #

length :: ListItem v a -> Int #

elem :: Eq a => a -> ListItem v a -> Bool #

maximum :: Ord a => ListItem v a -> a #

minimum :: Ord a => ListItem v a -> a #

sum :: Num a => ListItem v a -> a #

product :: Num a => ListItem v a -> a #

Traversable (ListItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

traverse :: Applicative f => (a -> f b) -> ListItem v a -> f (ListItem v b) #

sequenceA :: Applicative f => ListItem v (f a) -> f (ListItem v a) #

mapM :: Monad m => (a -> m b) -> ListItem v a -> m (ListItem v b) #

sequence :: Monad m => ListItem v (m a) -> m (ListItem v a) #

Eq a => Eq (ListItem v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

(==) :: ListItem v a -> ListItem v a -> Bool #

(/=) :: ListItem v a -> ListItem v a -> Bool #

Show a => Show (ListItem v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

showsPrec :: Int -> ListItem v a -> ShowS #

show :: ListItem v a -> String #

showList :: [ListItem v a] -> ShowS #

HasTrailingWhitespace (ListItem v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

HasNewlines (ListItem v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

data SetItem (v :: [*]) a Source #

a or *a

Used to construct sets, e.g. { 1, x, **c }

https://docs.python.org/3/reference/expressions.html#set-displays

Instances
Validated SetItem Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

unvalidated :: Getter (SetItem v a) (SetItem [] a) Source #

HasExprs SetItem Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

_Exprs :: Traversal (SetItem v a) (SetItem [] a) (Expr v a) (Expr [] a) Source #

AsSetItem SetItem Source # 
Instance details

Defined in Language.Python.DSL

StarSyntax Expr SetItem Source #

See set_

Instance details

Defined in Language.Python.DSL

Methods

s_ :: Raw Expr -> Raw SetItem Source #

Functor (SetItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fmap :: (a -> b) -> SetItem v a -> SetItem v b #

(<$) :: a -> SetItem v b -> SetItem v a #

Foldable (SetItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fold :: Monoid m => SetItem v m -> m #

foldMap :: Monoid m => (a -> m) -> SetItem v a -> m #

foldr :: (a -> b -> b) -> b -> SetItem v a -> b #

foldr' :: (a -> b -> b) -> b -> SetItem v a -> b #

foldl :: (b -> a -> b) -> b -> SetItem v a -> b #

foldl' :: (b -> a -> b) -> b -> SetItem v a -> b #

foldr1 :: (a -> a -> a) -> SetItem v a -> a #

foldl1 :: (a -> a -> a) -> SetItem v a -> a #

toList :: SetItem v a -> [a] #

null :: SetItem v a -> Bool #

length :: SetItem v a -> Int #

elem :: Eq a => a -> SetItem v a -> Bool #

maximum :: Ord a => SetItem v a -> a #

minimum :: Ord a => SetItem v a -> a #

sum :: Num a => SetItem v a -> a #

product :: Num a => SetItem v a -> a #

Traversable (SetItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

traverse :: Applicative f => (a -> f b) -> SetItem v a -> f (SetItem v b) #

sequenceA :: Applicative f => SetItem v (f a) -> f (SetItem v a) #

mapM :: Monad m => (a -> m b) -> SetItem v a -> m (SetItem v b) #

sequence :: Monad m => SetItem v (m a) -> m (SetItem v a) #

Eq a => Eq (SetItem v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

(==) :: SetItem v a -> SetItem v a -> Bool #

(/=) :: SetItem v a -> SetItem v a -> Bool #

Show a => Show (SetItem v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

showsPrec :: Int -> SetItem v a -> ShowS #

show :: SetItem v a -> String #

showList :: [SetItem v a] -> ShowS #

HasTrailingWhitespace (SetItem v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

HasNewlines (SetItem v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

data TupleItem (v :: [*]) a Source #

a or *a

Used to construct tuples, e.g. (1, x, **c)

Instances
Validated TupleItem Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

unvalidated :: Getter (TupleItem v a) (TupleItem [] a) Source #

HasExprs TupleItem Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

_Exprs :: Traversal (TupleItem v a) (TupleItem [] a) (Expr v a) (Expr [] a) Source #

AsTupleItem TupleItem Source # 
Instance details

Defined in Language.Python.DSL

StarSyntax Expr TupleItem Source #

See tuple_

Instance details

Defined in Language.Python.DSL

Methods

s_ :: Raw Expr -> Raw TupleItem Source #

Functor (TupleItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fmap :: (a -> b) -> TupleItem v a -> TupleItem v b #

(<$) :: a -> TupleItem v b -> TupleItem v a #

Foldable (TupleItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fold :: Monoid m => TupleItem v m -> m #

foldMap :: Monoid m => (a -> m) -> TupleItem v a -> m #

foldr :: (a -> b -> b) -> b -> TupleItem v a -> b #

foldr' :: (a -> b -> b) -> b -> TupleItem v a -> b #

foldl :: (b -> a -> b) -> b -> TupleItem v a -> b #

foldl' :: (b -> a -> b) -> b -> TupleItem v a -> b #

foldr1 :: (a -> a -> a) -> TupleItem v a -> a #

foldl1 :: (a -> a -> a) -> TupleItem v a -> a #

toList :: TupleItem v a -> [a] #

null :: TupleItem v a -> Bool #

length :: TupleItem v a -> Int #

elem :: Eq a => a -> TupleItem v a -> Bool #

maximum :: Ord a => TupleItem v a -> a #

minimum :: Ord a => TupleItem v a -> a #

sum :: Num a => TupleItem v a -> a #

product :: Num a => TupleItem v a -> a #

Traversable (TupleItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

traverse :: Applicative f => (a -> f b) -> TupleItem v a -> f (TupleItem v b) #

sequenceA :: Applicative f => TupleItem v (f a) -> f (TupleItem v a) #

mapM :: Monad m => (a -> m b) -> TupleItem v a -> m (TupleItem v b) #

sequence :: Monad m => TupleItem v (m a) -> m (TupleItem v a) #

Eq a => Eq (TupleItem v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

(==) :: TupleItem v a -> TupleItem v a -> Bool #

(/=) :: TupleItem v a -> TupleItem v a -> Bool #

Show a => Show (TupleItem v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

showsPrec :: Int -> TupleItem v a -> ShowS #

show :: TupleItem v a -> String #

showList :: [TupleItem v a] -> ShowS #

HasTrailingWhitespace (TupleItem v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

HasNewlines (TupleItem v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Subscripts

data Subscript (v :: [*]) a Source #

Syntax for things that can be used as subscripts (inside the square brackets)

e.g.

a[b]
a[:]
a[b:]
a[:b]
a[b:c]
a[b:c:d]

https://docs.python.org/3/reference/expressions.html#subscriptions

Constructors

SubscriptExpr (Expr v a) 
SubscriptSlice (Maybe (Expr v a)) Colon (Maybe (Expr v a)) (Maybe (Colon, Maybe (Expr v a))) 
Instances
Functor (Subscript v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fmap :: (a -> b) -> Subscript v a -> Subscript v b #

(<$) :: a -> Subscript v b -> Subscript v a #

Foldable (Subscript v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

fold :: Monoid m => Subscript v m -> m #

foldMap :: Monoid m => (a -> m) -> Subscript v a -> m #

foldr :: (a -> b -> b) -> b -> Subscript v a -> b #

foldr' :: (a -> b -> b) -> b -> Subscript v a -> b #

foldl :: (b -> a -> b) -> b -> Subscript v a -> b #

foldl' :: (b -> a -> b) -> b -> Subscript v a -> b #

foldr1 :: (a -> a -> a) -> Subscript v a -> a #

foldl1 :: (a -> a -> a) -> Subscript v a -> a #

toList :: Subscript v a -> [a] #

null :: Subscript v a -> Bool #

length :: Subscript v a -> Int #

elem :: Eq a => a -> Subscript v a -> Bool #

maximum :: Ord a => Subscript v a -> a #

minimum :: Ord a => Subscript v a -> a #

sum :: Num a => Subscript v a -> a #

product :: Num a => Subscript v a -> a #

Traversable (Subscript v) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

traverse :: Applicative f => (a -> f b) -> Subscript v a -> f (Subscript v b) #

sequenceA :: Applicative f => Subscript v (f a) -> f (Subscript v a) #

mapM :: Monad m => (a -> m b) -> Subscript v a -> m (Subscript v b) #

sequence :: Monad m => Subscript v (m a) -> m (Subscript v a) #

Eq a => Eq (Subscript v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

(==) :: Subscript v a -> Subscript v a -> Bool #

(/=) :: Subscript v a -> Subscript v a -> Bool #

Show a => Show (Subscript v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

Methods

showsPrec :: Int -> Subscript v a -> ShowS #

show :: Subscript v a -> String #

showList :: [Subscript v a] -> ShowS #

HasTrailingWhitespace (Subscript v a) Source # 
Instance details

Defined in Language.Python.Syntax.Expr

HasNewlines (Subscript v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines