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

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.AST.Gen.Exprs

Contents

Description

Generation of expression-level AST fragments for refactorings. The bindings defined here create a the annotated version of the AST constructor with the same name. For example, mkApp creates the annotated version of the App AST constructor.

Synopsis

Expressions

mkVar :: Name dom -> Expr dom Source #

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

mkLit :: Literal dom -> Expr dom Source #

Create a literal expression ( 42 )

mkInfixApp :: Expr dom -> Operator dom -> Expr dom -> Expr dom Source #

Create a infix operator application expression ( a + b )

mkPrefixApp :: Operator dom -> Expr dom -> Expr dom Source #

Create a prefix operator application expression ( -x )

mkApp :: Expr dom -> Expr dom -> Expr dom Source #

Create a function application expression ( f 4 )

mkLambda :: [Pattern dom] -> Expr dom -> Expr dom Source #

Create a lambda expression ( \a b -> a + b )

mkLet :: [LocalBind dom] -> Expr dom -> Expr dom Source #

Create a local binding ( let x = 2; y = 3 in e x y )

mkIf :: Expr dom -> Expr dom -> Expr dom -> Expr dom Source #

Create a if expression ( if a then b else c )

mkMultiIf :: [GuardedCaseRhs dom] -> Expr dom Source #

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

mkCase :: Expr dom -> [Alt dom] -> Expr dom Source #

Create a pattern matching expression ( case expr of pat1 -> expr1; pat2 -> expr2 )

mkDoBlock :: [Stmt dom] -> Expr dom Source #

Create a do-notation expressions ( do x <- act1; act2 )

mkTuple :: [Expr dom] -> Expr dom Source #

Create a tuple expression ( (e1, e2, e3) )

mkUnboxedTuple :: [Expr dom] -> Expr dom Source #

Create a unboxed tuple expression ( (# e1, e2, e3 #) )

mkTupleSection :: [Maybe (Expr dom)] -> Expr dom Source #

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

mkTupleUnboxedSection :: [Maybe (Expr dom)] -> Expr dom Source #

Create a unboxed tuple section, enabled with TupleSections ( (#a,,b#) ). One of the elements must be missing.

mkList :: [Expr dom] -> Expr dom Source #

Create a list expression: [1,2,3]

mkParArray :: [Expr dom] -> Expr dom Source #

Create a parallel array expression: [: 1,2,3 :]

mkParen :: Expr dom -> Expr dom Source #

Create a parenthesized expression: ( a + b )

mkLeftSection :: Expr dom -> Operator dom -> Expr dom Source #

Create a left operator section: (1+)

mkRightSection :: Operator dom -> Expr dom -> Expr dom Source #

Create a right operator section: (+1)

mkRecCon :: Name dom -> [FieldUpdate dom] -> Expr dom Source #

Create a record value construction: Point { x = 3, y = -2 }

mkRecUpdate :: Expr dom -> [FieldUpdate dom] -> Expr dom Source #

Create a record value update: p1 { x = 3, y = -2 }

mkEnum :: Expr dom -> Maybe (Expr dom) -> Maybe (Expr dom) -> Expr dom Source #

Create a enumeration expression ( [1,3..10] )

mkParArrayEnum :: Expr dom -> Maybe (Expr dom) -> Expr dom -> Expr dom Source #

Create a parallel array enumeration ( [: 1,3 .. 10 :] )

mkListComp :: Expr dom -> [ListCompBody dom] -> Expr dom Source #

Create a list comprehension ( [ (x, y) | x <- xs | y <- ys ] )

mkParArrayComp :: Expr dom -> [ListCompBody dom] -> Expr dom Source #

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

mkExprTypeSig :: Expr dom -> Type dom -> Expr dom Source #

Create a explicit type signature ( x :: Int )

mkExplicitTypeApp :: Expr dom -> Type dom -> Expr dom Source #

Create a explicit type application ( show @Integer (read "5") )

mkVarQuote :: Name dom -> Expr dom Source #

'x for template haskell reifying of expressions

mkTypeQuote :: Name dom -> Expr dom Source #

''T for template haskell reifying of types

mkBracketExpr :: Bracket dom -> Expr dom Source #

Create a template haskell bracket expression

mkSpliceExpr :: Splice dom -> Expr dom Source #

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

mkQuasiQuoteExpr :: QuasiQuote dom -> Expr dom Source #

Create a template haskell quasi quote expression, for example: [quoter| a + b ]

mkExprPragma :: ExprPragma dom -> Expr dom -> Expr dom Source #

Creates a pragma that marks an expression.

mkProcExpr :: Pattern dom -> Cmd dom -> Expr dom Source #

Create a arrow definition: proc a -> f -< a+1

mkArrowApp :: Expr dom -> ArrowApp dom -> Expr dom -> Expr dom Source #

Create a arrow definition: proc a -> f -< a+1

mkLambdaCase :: [Alt dom] -> Expr dom Source #

Create a lambda case ( case 0 -> 1; 1 -> 2 )

mkStaticPointer :: Expr dom -> Expr dom Source #

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

Field updates

mkFieldUpdate :: Name dom -> Expr dom -> FieldUpdate dom Source #

Create a update of a field ( x = 1 )

mkFieldPun :: Name dom -> FieldUpdate dom Source #

Create a update the field to the value of the same name ( x )

mkFieldWildcard :: FieldUpdate dom Source #

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

Pattern matching and guards

mkAlt :: Pattern dom -> CaseRhs dom -> Maybe (LocalBinds dom) -> Alt dom Source #

Create a clause of case expression ( Just x -> x + 1 )

mkCaseRhs :: Expr dom -> CaseRhs dom Source #

Create a unguarded right-hand side a pattern match ( -> 3 )

mkGuardedCaseRhss :: [GuardedCaseRhs dom] -> CaseRhs dom Source #

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

mkGuardedCaseRhs :: [RhsGuard dom] -> Expr dom -> GuardedCaseRhs dom Source #

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

Pragmas that can be applied to expressions

mkCorePragma :: String -> ExprPragma dom Source #

Creates a CORE pragma for adding notes to expressions.

mkSccPragma :: String -> ExprPragma dom Source #

Creates an SCC pragma for defining cost centers for profiling

mkGeneratedPragma :: SourceRange dom -> ExprPragma dom Source #

Creates a pragma that describes if an expression was generated from a code fragment by an external tool ( {-# GENERATED "Happy.y" 1:15-1:25 #-} )

mkSourceRange :: String -> Integer -> Integer -> Integer -> Integer -> SourceRange dom Source #

Create a in-AST source ranges (for generated pragmas)

Commands

mkArrowAppCmd :: Expr dom -> ArrowApp dom -> Expr dom -> Cmd dom Source #

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

mkArrowFromCmd :: Expr dom -> [Cmd dom] -> Cmd dom Source #

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

mkAppCmd :: Cmd dom -> Expr dom -> Cmd dom Source #

A function application command

mkInfixCmd :: Cmd dom -> Name dom -> Cmd dom -> Cmd dom Source #

An infix command application

mkLambdaCmd :: [Pattern dom] -> Cmd dom -> Cmd dom Source #

A lambda command

mkParenCmd :: Cmd dom -> Cmd dom Source #

A parenthesized command

mkCaseCmd :: Expr dom -> [CmdAlt dom] -> Cmd dom Source #

A pattern match command

mkIfCmd :: Expr dom -> Cmd dom -> Cmd dom -> Cmd dom Source #

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

mkLetCmd :: [LocalBind dom] -> Cmd dom -> Cmd dom Source #

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

mkDoCmd :: [CmdStmt dom] -> Cmd dom Source #

A do-notation in a command

mkLeftAppl :: ArrowApp dom Source #

Left arrow application: -<

mkRightAppl :: ArrowApp dom Source #

Right arrow application: >-

mkLeftHighAppl :: ArrowApp dom Source #

Left arrow high application: -<<

mkRightHighAppl :: ArrowApp dom Source #

Right arrow high application: >>-