hpython-0.1: Syntax tree and DSL for Python

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

Language.Python.Syntax.Statement

Contents

Description

 
Synopsis

Statements

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

Instances
Validated Statement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

HasTrailingNewline Statement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

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 #

HasBlocks Statement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Blocks :: Traversal (Statement v a) (Statement [] a) (Block v a) (Block [] a) Source #

HasWith Statement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_With :: Prism (Statement v a) (Statement [] a) (With v a) (With [] a) Source #

HasClassDef Statement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_ClassDef :: Prism (Statement v a) (Statement [] a) (ClassDef v a) (ClassDef [] a) Source #

HasFor Statement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_For :: Prism (Statement v a) (Statement [] a) (For v a) (For [] a) Source #

HasTryFinally Statement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_TryFinally :: Prism (Statement v a) (Statement [] a) (TryFinally v a) (TryFinally [] a) Source #

HasTryExcept Statement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_TryExcept :: Prism (Statement v a) (Statement [] a) (TryExcept v a) (TryExcept [] a) Source #

HasIf Statement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_If :: Prism (Statement v a) (Statement [] a) (If v a) (If [] a) Source #

HasWhile Statement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_While :: Prism (Statement v a) (Statement [] a) (While v a) (While [] a) Source #

HasFundef Statement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_Fundef :: Prism (Statement v a) (Statement [] a) (Fundef v a) (Fundef [] a) Source #

HasCompoundStatement Statement Source # 
Instance details

Defined in Language.Python.Optics

AsLine Statement Source # 
Instance details

Defined in Language.Python.DSL

Functor (Statement v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

Foldable (Statement v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

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

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

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

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

null :: Statement v a -> Bool #

length :: Statement v a -> Int #

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

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

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

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

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

Traversable (Statement v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

Defined in Language.Python.Syntax.Statement

Methods

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

show :: Statement v a -> String #

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

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

Defined in Language.Python.Syntax.Statement

Methods

plate :: Traversal' (Statement [] a) (Statement [] a)

HasNewlines (Statement v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Methods

_Newlines :: Traversal' (Statement v a) Newline Source #

HasIndents (Statement ([] :: [Type]) a) a Source # 
Instance details

Defined in Language.Python.Optics.Indents

Methods

_Indents :: Traversal' (Statement [] a) (Indents a) Source #

Traversals

class HasStatements s where Source #

Traversal over all the Statements in a term

Methods

_Statements :: Traversal (s v a) (s '[] a) (Statement v a) (Statement '[] a) Source #

Instances
HasStatements Suite Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Statements :: Traversal (Suite v a) (Suite [] a) (Statement v a) (Statement [] a) Source #

HasStatements Block Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Statements :: Traversal (Block v a) (Block [] a) (Statement v a) (Statement [] a) Source #

HasStatements Module Source # 
Instance details

Defined in Language.Python.Syntax.Module

Methods

_Statements :: Traversal (Module v a) (Module [] a) (Statement v a) (Statement [] a) Source #

HasStatements Line Source # 
Instance details

Defined in Language.Python.DSL

Methods

_Statements :: Traversal (Line v a) (Line [] a) (Statement v a) (Statement [] a) Source #

Decorators

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

Constructors

Decorator 

Fields

Instances
Validated Decorator Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

unvalidated :: Getter (Decorator v a) (Decorator [] 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 #

Functor (Decorator v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

Foldable (Decorator v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

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

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

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

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

null :: Decorator v a -> Bool #

length :: Decorator v a -> Int #

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

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

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

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

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

Traversable (Decorator v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

Defined in Language.Python.Syntax.Statement

Methods

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

show :: Decorator v a -> String #

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

HasNewlines (Decorator v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Methods

_Newlines :: Traversal' (Decorator v a) Newline Source #

HasIndents (Decorator ([] :: [Type]) a) a Source # 
Instance details

Defined in Language.Python.Optics.Indents

Methods

_Indents :: Traversal' (Decorator [] a) (Indents a) Source #

Compound statements

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

Constructors

Fundef

https://docs.python.org/3.5/reference/compound_stmts.html#function-definitions

https://docs.python.org/3.5/reference/compound_stmts.html#coroutine-function-definition

Fields

If

https://docs.python.org/3.5/reference/compound_stmts.html#the-if-statement

Fields

While

https://docs.python.org/3.5/reference/compound_stmts.html#the-while-statement

Fields

TryExcept

https://docs.python.org/3.5/reference/compound_stmts.html#the-try-statement

Fields

TryFinally

https://docs.python.org/3.5/reference/compound_stmts.html#the-try-statement

For

https://docs.python.org/3.5/reference/compound_stmts.html#the-for-statement

https://docs.python.org/3.5/reference/compound_stmts.html#the-async-for-statement

Fields

ClassDef

https://docs.python.org/3.5/reference/compound_stmts.html#class-definitions

Fields

With

https://docs.python.org/3.5/reference/compound_stmts.html#the-with-statement

https://docs.python.org/3.5/reference/compound_stmts.html#the-async-with-statement

Fields

Instances
Validated CompoundStatement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

HasTrailingNewline CompoundStatement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

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 #

HasBlocks CompoundStatement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Blocks :: Traversal (CompoundStatement v a) (CompoundStatement [] a) (Block v a) (Block [] a) Source #

HasWith CompoundStatement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_With :: Prism (CompoundStatement v a) (CompoundStatement [] a) (With v a) (With [] a) Source #

HasClassDef CompoundStatement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_ClassDef :: Prism (CompoundStatement v a) (CompoundStatement [] a) (ClassDef v a) (ClassDef [] a) Source #

HasFor CompoundStatement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_For :: Prism (CompoundStatement v a) (CompoundStatement [] a) (For v a) (For [] a) Source #

HasTryFinally CompoundStatement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_TryFinally :: Prism (CompoundStatement v a) (CompoundStatement [] a) (TryFinally v a) (TryFinally [] a) Source #

HasTryExcept CompoundStatement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_TryExcept :: Prism (CompoundStatement v a) (CompoundStatement [] a) (TryExcept v a) (TryExcept [] a) Source #

HasIf CompoundStatement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_If :: Prism (CompoundStatement v a) (CompoundStatement [] a) (If v a) (If [] a) Source #

HasWhile CompoundStatement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_While :: Prism (CompoundStatement v a) (CompoundStatement [] a) (While v a) (While [] a) Source #

HasFundef CompoundStatement Source # 
Instance details

Defined in Language.Python.Optics

Methods

_Fundef :: Prism (CompoundStatement v a) (CompoundStatement [] a) (Fundef v a) (Fundef [] a) Source #

HasCompoundStatement CompoundStatement Source # 
Instance details

Defined in Language.Python.Optics

AsLine CompoundStatement Source # 
Instance details

Defined in Language.Python.DSL

Functor (CompoundStatement v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

Foldable (CompoundStatement v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

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

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

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

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

null :: CompoundStatement v a -> Bool #

length :: CompoundStatement v a -> Int #

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

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

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

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

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

Traversable (CompoundStatement v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

Defined in Language.Python.Syntax.Statement

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

Defined in Language.Python.Syntax.Statement

HasNewlines (CompoundStatement v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Methods

_Newlines :: Traversal' (CompoundStatement v a) Newline Source #

HasIndents (CompoundStatement ([] :: [Type]) a) a Source # 
Instance details

Defined in Language.Python.Optics.Indents

Methods

_Indents :: Traversal' (CompoundStatement [] a) (Indents a) Source #

Small statements

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

See simpl_stmt at https://docs.python.org/3.5/reference/grammar.html. The grammar has the terminology mixed up - it should really be called small_stmt there.

Instances
Validated SmallStatement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

HasTrailingNewline SmallStatement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

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 #

HasBlocks SmallStatement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Blocks :: Traversal (SmallStatement v a) (SmallStatement [] a) (Block v a) (Block [] a) Source #

AsLine SmallStatement Source # 
Instance details

Defined in Language.Python.DSL

Functor (SmallStatement v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

Foldable (SmallStatement v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

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

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

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

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

null :: SmallStatement v a -> Bool #

length :: SmallStatement v a -> Int #

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

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

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

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

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

Traversable (SmallStatement v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

Defined in Language.Python.Syntax.Statement

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

Defined in Language.Python.Syntax.Statement

HasNewlines (SmallStatement v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Methods

_Newlines :: Traversal' (SmallStatement v a) Newline Source #

HasIndents (SmallStatement ([] :: [Type]) a) a Source # 
Instance details

Defined in Language.Python.Optics.Indents

Methods

_Indents :: Traversal' (SmallStatement [] a) (Indents a) Source #

Simple statements

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

Constructors

Return a [Whitespace] (Maybe (Expr v a))
'return' <spaces> [<expr>]

https://docs.python.org/3.5/reference/simple_stmts.html#the-return-statement

Expr a (Expr v a)
<expr>

https://docs.python.org/3.5/reference/simple_stmts.html#expression-statements

Assign a (Expr v a) (NonEmpty (Equals, Expr v a))
<expr> ('=' <spaces> <expr>)+

https://docs.python.org/3.5/reference/simple_stmts.html#assignment-statements

AugAssign a (Expr v a) (AugAssign a) (Expr v a)
<expr> <augassign> <expr>

https://docs.python.org/3.5/reference/simple_stmts.html#augmented-assignment-statements

Pass a [Whitespace]
'pass' <spaces>

https://docs.python.org/3.5/reference/simple_stmts.html#the-pass-statement

Break a [Whitespace]
'break' <spaces>

https://docs.python.org/3.5/reference/simple_stmts.html#the-break-statement

Continue a [Whitespace]
'continue' <spaces>

https://docs.python.org/3.5/reference/simple_stmts.html#the-continue-statement

Global a (NonEmpty Whitespace) (CommaSep1 (Ident v a))
'global' <spaces> <idents>

https://docs.python.org/3.5/reference/simple_stmts.html#the-global-statement

Nonlocal a (NonEmpty Whitespace) (CommaSep1 (Ident v a))
'nonlocal' <spaces> <idents>

https://docs.python.org/3.5/reference/simple_stmts.html#the-nonlocal-statement

Del a [Whitespace] (CommaSep1' (Expr v a))
'del' <spaces> <exprs>

https://docs.python.org/3.5/reference/simple_stmts.html#the-del-statement

Import a (NonEmpty Whitespace) (CommaSep1 (ImportAs (ModuleName v) v a))
'import' <spaces> <modulenames>

https://docs.python.org/3.5/reference/simple_stmts.html#the-import-statement

From a [Whitespace] (RelativeModuleName v a) [Whitespace] (ImportTargets v a)
'from' <spaces> <relative_module_name> 'import' <spaces> <import_targets>

https://docs.python.org/3.5/reference/simple_stmts.html#the-import-statement

Raise a [Whitespace] (Maybe (Expr v a, Maybe ([Whitespace], Expr v a)))
'raise' <spaces> [<expr> ['as' <spaces> <expr>]]

https://docs.python.org/3.5/reference/simple_stmts.html#the-raise-statement

Assert a [Whitespace] (Expr v a) (Maybe (Comma, Expr v a))
'assert' <spaces> <expr> [',' <spaces> <expr>]

https://docs.python.org/3.5/reference/simple_stmts.html#the-assert-statement

Instances
Validated SimpleStatement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

unvalidated :: Getter (SimpleStatement v a) (SimpleStatement [] 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 #

AsLine SimpleStatement Source # 
Instance details

Defined in Language.Python.DSL

Functor (SimpleStatement v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

Foldable (SimpleStatement v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

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

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

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

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

null :: SimpleStatement v a -> Bool #

length :: SimpleStatement v a -> Int #

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

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

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

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

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

Traversable (SimpleStatement v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

Defined in Language.Python.Syntax.Statement

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

Defined in Language.Python.Syntax.Statement

Generic (SimpleStatement v a) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Associated Types

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

Methods

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

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

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

Defined in Language.Python.Syntax.Statement

Methods

plate :: Traversal' (SimpleStatement [] a) (SimpleStatement [] a)

HasNewlines (SimpleStatement v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Methods

_Newlines :: Traversal' (SimpleStatement v a) Newline Source #

type Rep (SimpleStatement v a) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

type Rep (SimpleStatement v a) = D1 (MetaData "SimpleStatement" "Language.Python.Syntax.Statement" "hpython-0.1-inplace" False) (((C1 (MetaCons "Return" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Expr v a))))) :+: (C1 (MetaCons "Expr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a))) :+: C1 (MetaCons "Assign" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (Equals, Expr v a))))))) :+: ((C1 (MetaCons "AugAssign" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AugAssign a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a)))) :+: C1 (MetaCons "Pass" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]))) :+: (C1 (MetaCons "Break" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :+: C1 (MetaCons "Continue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]))))) :+: ((C1 (MetaCons "Global" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty Whitespace)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CommaSep1 (Ident v a))))) :+: (C1 (MetaCons "Nonlocal" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty Whitespace)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CommaSep1 (Ident v a))))) :+: C1 (MetaCons "Del" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CommaSep1' (Expr v a))))))) :+: ((C1 (MetaCons "Import" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty Whitespace)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CommaSep1 (ImportAs (ModuleName v) v a))))) :+: C1 (MetaCons "From" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelativeModuleName v a)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ImportTargets v a)))))) :+: (C1 (MetaCons "Raise" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Expr v a, Maybe ([Whitespace], Expr v a)))))) :+: C1 (MetaCons "Assert" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr v a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Comma, Expr v a)))))))))

with ... as ...

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

Constructors

WithItem 

Fields

Instances
Validated WithItem Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

unvalidated :: Getter (WithItem v a) (WithItem [] 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 #

AsWithItem WithItem Source # 
Instance details

Defined in Language.Python.DSL

As Expr Expr WithItem Source #

See with_

Instance details

Defined in Language.Python.DSL

Methods

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

Functor (WithItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

Foldable (WithItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

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

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

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

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

null :: WithItem v a -> Bool #

length :: WithItem v a -> Int #

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

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

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

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

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

Traversable (WithItem v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

Defined in Language.Python.Syntax.Statement

Methods

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

show :: WithItem v a -> String #

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

HasNewlines (WithItem v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Methods

_Newlines :: Traversal' (WithItem v a) Newline Source #

Lenses

withItemAnn :: forall v a. Lens' (WithItem v a) a Source #

withItemValue :: forall v a. Lens' (WithItem v a) (Expr v a) Source #

withItemBinder :: forall v a. Lens' (WithItem v a) (Maybe ([Whitespace], Expr v a)) Source #

except ... as ...

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

Constructors

ExceptAs 

Fields

Instances
Validated ExceptAs Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

unvalidated :: Getter (ExceptAs v a) (ExceptAs [] 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 #

AsExceptAs ExceptAs Source # 
Instance details

Defined in Language.Python.DSL

As Expr Ident ExceptAs Source #

See exceptAs_

Instance details

Defined in Language.Python.DSL

Methods

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

Functor (ExceptAs v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

Foldable (ExceptAs v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

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

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

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

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

null :: ExceptAs v a -> Bool #

length :: ExceptAs v a -> Int #

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

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

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

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

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

Traversable (ExceptAs v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

Defined in Language.Python.Syntax.Statement

Methods

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

show :: ExceptAs v a -> String #

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

HasNewlines (ExceptAs v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Methods

_Newlines :: Traversal' (ExceptAs v a) Newline Source #

Lenses

exceptAsAnn :: forall v a. Lens' (ExceptAs v a) a Source #

exceptAsExpr :: forall v a. Lens' (ExceptAs v a) (Expr v a) Source #

exceptAsName :: forall v a. Lens' (ExceptAs v a) (Maybe ([Whitespace], Ident v a)) Source #

Suites

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

A compound statement consists of one or more clauses. A clause consists of a header and a suite.

Constructors

SuiteOne a Colon (SmallStatement v a) 
SuiteMany a Colon (Maybe (Comment a)) Newline (Block v a) 
Instances
Validated Suite Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

HasTrailingNewline Suite Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

trailingNewline :: Traversal' (Suite v a) Newline Source #

setTrailingNewline :: Suite v a -> Newline -> Suite v 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 #

HasBlocks Suite Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Blocks :: Traversal (Suite v a) (Suite [] a) (Block v a) (Block [] a) Source #

HasStatements Suite Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Statements :: Traversal (Suite v a) (Suite [] a) (Statement v a) (Statement [] a) Source #

Functor (Suite v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

Foldable (Suite v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

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

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

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

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

null :: Suite v a -> Bool #

length :: Suite v a -> Int #

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

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

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

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

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

Traversable (Suite v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

Defined in Language.Python.Syntax.Statement

Methods

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

show :: Suite v a -> String #

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

HasNewlines (Suite v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Methods

_Newlines :: Traversal' (Suite v a) Newline Source #

HasIndents (Suite ([] :: [Type]) a) a Source # 
Instance details

Defined in Language.Python.Optics.Indents

Methods

_Indents :: Traversal' (Suite [] a) (Indents a) Source #

Blocks

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

A Block is an indented multi-line chunk of code, forming part of a Suite.

Constructors

Block 

Fields

Instances
Validated Block Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

HasTrailingNewline Block Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

trailingNewline :: Traversal' (Block v a) Newline Source #

setTrailingNewline :: Block v a -> Newline -> Block v 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 #

HasStatements Block Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Statements :: Traversal (Block v a) (Block [] a) (Statement v a) (Statement [] a) Source #

Functor (Block v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

Foldable (Block v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

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

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

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

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

null :: Block v a -> Bool #

length :: Block v a -> Int #

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

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

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

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

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

Traversable (Block v) Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

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

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

Defined in Language.Python.Syntax.Statement

Methods

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

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

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

Defined in Language.Python.Syntax.Statement

Methods

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

show :: Block v a -> String #

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

HasNewlines (Block v a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Methods

_Newlines :: Traversal' (Block v a) Newline Source #

HasIndents (Block ([] :: [Type]) a) a Source # 
Instance details

Defined in Language.Python.Optics.Indents

Methods

_Indents :: Traversal' (Block [] a) (Indents a) Source #

Lenses

blockBlankLines :: forall v a. Lens' (Block v a) [(Blank a, Newline)] Source #

blockHead :: forall v a. Lens' (Block v a) (Statement v a) Source #

blockTail :: forall v a. Lens' (Block v a) [Either (Blank a, Newline) (Statement v a)] Source #

Traversals

class HasBlocks s where Source #

Methods

_Blocks :: Traversal (s v a) (s '[] a) (Block v a) (Block '[] a) Source #

Traversal targeting all the Blocks in a structure

Instances
HasBlocks CompoundStatement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Blocks :: Traversal (CompoundStatement v a) (CompoundStatement [] a) (Block v a) (Block [] a) Source #

HasBlocks Suite Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Blocks :: Traversal (Suite v a) (Suite [] a) (Block v a) (Block [] a) Source #

HasBlocks Statement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Blocks :: Traversal (Statement v a) (Statement [] a) (Block v a) (Block [] a) Source #

HasBlocks SmallStatement Source # 
Instance details

Defined in Language.Python.Syntax.Statement

Methods

_Blocks :: Traversal (SmallStatement v a) (SmallStatement [] a) (Block v a) (Block [] a) Source #