haskell-tools-rewrite-0.9.0.0: Facilities for generating new parts of the Haskell-Tools AST

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.Rewrite.Match.Exprs

Contents

Description

UPattern matching expression-level AST fragments for refactorings.

Synopsis

Expressions

pattern Var :: forall dom. Name dom -> Expr dom Source #

An expression for a variable or a data constructor ( a )

pattern Lit :: forall dom. Literal dom -> Expr dom Source #

A literal expression ( 42 )

pattern InfixApp :: forall dom. Expr dom -> Operator dom -> Expr dom -> Expr dom Source #

An infix operator application ( a + b )

pattern PrefixApp :: forall dom. Operator dom -> Expr dom -> Expr dom Source #

Prefix operator application ( -x )

pattern App :: forall dom. Expr dom -> Expr dom -> Expr dom Source #

Function application ( f 4 )

pattern Lambda :: forall dom. PatternList dom -> Expr dom -> Expr dom Source #

Lambda expression ( \a b -> a + b )

pattern Let :: forall dom. LocalBindList dom -> Expr dom -> Expr dom Source #

Local binding ( let x = 2; y = 3 in e x y )

pattern If :: forall dom. Expr dom -> Expr dom -> Expr dom -> Expr dom Source #

If expression ( if a then b else c )

pattern MultiIf :: forall dom. GuardedCaseRhsList dom -> Expr dom Source #

Multi way if expressions with MultiWayIf extension ( if | guard1 -> expr1; guard2 -> expr2 )

pattern Case :: forall dom. Expr dom -> AltList dom -> Expr dom Source #

Pattern matching expression ( case expr of pat1 -> expr1; pat2 -> expr2 )

pattern Do :: forall dom. StmtList dom -> Expr dom Source #

Do-notation expressions ( do x <- act1; act2 )

pattern ParArrayComp :: forall dom. Expr dom -> ListCompBodyList dom -> Expr dom Source #

pattern Tuple :: forall dom. ExprList dom -> Expr dom Source #

Tuple expression ( (e1, e2, e3) )

pattern UnboxedTuple :: forall dom. ExprList dom -> Expr dom Source #

Unboxed tuple expression ( (# e1, e2, e3 #) )

pattern TupleSection :: forall dom. TupSecElemList dom -> Expr dom Source #

Tuple section, enabled with TupleSections ( (a,,b) ). One of the elements must be missing.

pattern UnboxedTupleSection :: forall dom. TupSecElemList dom -> Expr dom Source #

Unboxed tuple section enabled with TupleSections ( () ). One of the elements must be missing.

pattern List :: forall dom. ExprList dom -> Expr dom Source #

List expression: [1,2,3]

pattern ParArray :: forall dom. ExprList dom -> Expr dom Source #

Parallel array expression: [: 1,2,3 :]

pattern Paren :: forall dom. Expr dom -> Expr dom Source #

Parenthesized expression: ( a + b )

pattern LeftSection :: forall dom. Expr dom -> Operator dom -> Expr dom Source #

Left operator section: (1+)

pattern RightSection :: forall dom. Operator dom -> Expr dom -> Expr dom Source #

Right operator section: (+1)

pattern RecCon :: forall dom. Name dom -> FieldUpdateList dom -> Expr dom Source #

Record value construction: Point { x = 3, y = -2 }

pattern RecUpdate :: forall dom. Expr dom -> FieldUpdateList dom -> Expr dom Source #

Record value update: p1 { x = 3, y = -2 }

pattern Enum :: forall dom. Expr dom -> MaybeExpr dom -> MaybeExpr dom -> Expr dom Source #

Enumeration expression ( [1,3..10] )

pattern ParArrayEnum :: forall dom. Expr dom -> MaybeExpr dom -> Expr dom -> Expr dom Source #

Parallel array enumeration ( [: 1,3 .. 10 :] )

pattern ListComp :: forall dom. Expr dom -> ListCompBodyList dom -> Expr dom Source #

List comprehension ( [ (x, y) | x <- xs | y <- ys ] )

pattern ParArrayListComp :: forall dom. Expr dom -> ListCompBodyList dom -> Expr dom Source #

Parallel array comprehensions [: (x, y) | x <- xs , y <- ys :] enabled by ParallelArrays

pattern TypeSig :: forall dom. Expr dom -> Type dom -> Expr dom Source #

Explicit type signature ( x :: Int )

pattern ExplicitTypeApp :: forall dom. Expr dom -> Type dom -> Expr dom Source #

Explicit type application ( show @Integer (read "5") )

pattern VarQuote :: forall dom. Name dom -> Expr dom Source #

'x for template haskell reifying of expressions

pattern TypeQuote :: forall dom. Name dom -> Expr dom Source #

''T for template haskell reifying of types

pattern BracketExpr :: forall dom. Bracket dom -> Expr dom Source #

Template haskell bracket expression

pattern SpliceExpr :: forall dom. Splice dom -> Expr dom Source #

Template haskell splice expression, for example: $(gen a) or $x

pattern QuasiQuoteExpr :: forall dom. QuasiQuote dom -> Expr dom Source #

Template haskell quasi-quotation: [$quoter|str]

pattern ExprPragma :: forall dom. ExprPragma dom -> Expr dom -> Expr dom Source #

Template haskell quasi-quotation: [$quoter|str]

pattern Proc :: forall dom. Pattern dom -> Cmd dom -> Expr dom Source #

Arrow definition: proc a -> f -< a+1

pattern ArrowApp :: forall dom. Expr dom -> ArrowApp dom -> Expr dom -> Expr dom Source #

Arrow definition: proc a -> f -< a+1

pattern LambdaCase :: forall dom. AltList dom -> Expr dom Source #

Lambda case ( case 0 -> 1; 1 -> 2 )

pattern StaticPointer :: forall dom. Expr dom -> Expr dom Source #

Static pointer expression ( static e ). The inner expression must be closed (cannot have variables bound outside)

Field updates

pattern NormalFieldUpdate :: forall dom. Name dom -> Expr dom -> FieldUpdate dom Source #

Update of a field ( x = 1 )

pattern FieldPun :: forall dom. Name dom -> FieldUpdate dom Source #

Update the field to the value of the same name ( x )

pattern FieldWildcard :: forall dom. FieldWildcard dom -> FieldUpdate dom Source #

Update the fields of the bounded names to their values ( .. ). Must be the last initializer. Cannot be used in a record update expression.

Tuple sections

pattern TupSecPresent :: forall dom. Expr dom -> TupSecElem dom Source #

An existing element in a tuple section

pattern TupSecMissing :: forall dom. TupSecElem dom Source #

A missing element in a tuple section

Pattern matching and guards

pattern Alt :: forall dom. Pattern dom -> CaseRhs dom -> MaybeLocalBinds dom -> Alt dom Source #

Clause of case expression ( Just x -> x + 1 )

pattern CaseRhs :: forall dom. Expr dom -> CaseRhs dom Source #

Unguarded right-hand side a pattern match ( -> 3 )

pattern GuardedCaseRhss :: forall dom. GuardedCaseRhsList dom -> CaseRhs dom Source #

Guarded right-hand sides of a pattern match ( | x == 1 -> 3; | otherwise -> 4 )

pattern GuardedCaseRhs :: forall dom. RhsGuardList dom -> Expr dom -> GuardedCaseRhs dom Source #

A guarded right-hand side of pattern matches binding ( | x > 3 -> 2 )

Pragmas that can be applied to expressions

pattern CorePragma :: forall dom. String -> ExprPragma dom Source #

A CORE pragma for adding notes to expressions.

pattern SccPragma :: forall dom. String -> ExprPragma dom Source #

An SCC pragma for defining cost centers for profiling

pattern GeneratedPragma :: forall dom. SourceRange dom -> ExprPragma dom Source #

A pragma that describes if an expression was generated from a code fragment by an external tool ( {--} )

pattern SourceRange :: forall dom. String -> Integer -> Integer -> Integer -> Integer -> SourceRange dom Source #

In-AST source ranges (for generated pragmas)

Commands

pattern ArrowAppCmd :: forall dom. Expr dom -> ArrowApp dom -> Expr dom -> Cmd dom Source #

An arrow application command ( f -< x + 1 )

pattern ArrowFormCmd :: forall dom. Expr dom -> CmdList dom -> Cmd dom Source #

A form command ( (|untilA (increment -< x+y) (within 0.5 -< x)|) )

pattern AppCmd :: forall dom. Cmd dom -> Expr dom -> Cmd dom Source #

A function application command

pattern InfixCmd :: forall dom. Cmd dom -> Name dom -> Cmd dom -> Cmd dom Source #

An infix command application

pattern LambdaCmd :: forall dom. PatternList dom -> Cmd dom -> Cmd dom Source #

An infix command application

pattern ParenCmd :: forall dom. Cmd dom -> Cmd dom Source #

A parenthesized command

pattern CaseCmd :: forall dom. Expr dom -> CmdAltList dom -> Cmd dom Source #

A pattern match command

pattern IfCmd :: forall dom. Expr dom -> Cmd dom -> Cmd dom -> Cmd dom Source #

An if command ( if f x y then g -< x+1 else h -< y+2 )

pattern LetCmd :: forall dom. LocalBindList dom -> Cmd dom -> Cmd dom Source #

A local binding command ( let z = x+y )

pattern DoCmd :: forall dom. CmdStmtList dom -> Cmd dom Source #

A local binding command ( let z = x+y )

pattern LeftAppl :: forall dom. ArrowApp dom Source #

Left arrow application: -<

pattern RightAppl :: forall dom. ArrowApp dom Source #

Right arrow application: >-

pattern LeftHighApp :: forall dom. ArrowApp dom Source #

Left arrow high application: -<<

pattern RightHighApp :: forall dom. ArrowApp dom Source #

Right arrow high application: >>-