ghc-7.0.3: The GHC API

MkCore

Contents

Description

Handy functions for creating much Core syntax

Synopsis

Constructing normal syntax

mkCoreLet :: CoreBind -> CoreExpr -> CoreExprSource

Bind a binding group over an expression, using a let or case as appropriate (see CoreSyn)

mkCoreLets :: [CoreBind] -> CoreExpr -> CoreExprSource

Bind a list of binding groups over an expression. The leftmost binding group becomes the outermost group in the resulting expression

mkCoreApp :: CoreExpr -> CoreExpr -> CoreExprSource

Construct an expression which represents the application of one expression to the other

mkCoreApps :: CoreExpr -> [CoreExpr] -> CoreExprSource

Construct an expression which represents the application of a number of expressions to another. The leftmost expression in the list is applied first

mkCoreConApps :: DataCon -> [CoreExpr] -> CoreExprSource

Construct an expression which represents the application of a number of expressions to that of a data constructor expression. The leftmost expression in the list is applied first

mkCoreLams :: [CoreBndr] -> CoreExpr -> CoreExprSource

Create a lambda where the given expression has a number of variables bound over it. The leftmost binder is that bound by the outermost lambda in the result

mkWildValBinder :: Type -> IdSource

Make a wildcard binder. This is typically used when you need a binder that you expect to use only at a *binding* site. Do not use it at occurrence sites because it has a single, fixed unique, and it's very easy to get into difficulties with shadowing. That's why it is used so little.

Constructing boxed literals

mkWordExpr :: Integer -> CoreExprSource

Create a CoreExpr which will evaluate to the a Word with the given value

mkWordExprWord :: Word -> CoreExprSource

Create a CoreExpr which will evaluate to the given Word

mkIntExpr :: Integer -> CoreExprSource

Create a CoreExpr which will evaluate to the given Int

mkIntExprInt :: Int -> CoreExprSource

Create a CoreExpr which will evaluate to the given Int

mkIntegerExpr :: MonadThings m => Integer -> m CoreExprSource

Create a CoreExpr which will evaluate to the given Integer

mkFloatExpr :: Float -> CoreExprSource

Create a CoreExpr which will evaluate to the given Float

mkDoubleExpr :: Double -> CoreExprSource

Create a CoreExpr which will evaluate to the given Double

mkCharExpr :: Char -> CoreExprSource

Create a CoreExpr which will evaluate to the given Char

mkStringExpr :: MonadThings m => String -> m CoreExprSource

Create a CoreExpr which will evaluate to the given String

mkStringExprFS :: MonadThings m => FastString -> m CoreExprSource

Create a CoreExpr which will evaluate to a string morally equivalent to the given FastString

Constructing general big tuples

GHCs built in tuples can only go up to mAX_TUPLE_SIZE in arity, but we might concievably want to build such a massive tuple as part of the output of a desugaring stage (notably that for list comprehensions).

We call tuples above this size "big tuples", and emulate them by creating and pattern matching on >nested< tuples that are expressible by GHC.

Nesting policy: it's better to have a 2-tuple of 10-tuples (3 objects) than a 10-tuple of 2-tuples (11 objects), so we want the leaves of any construction to be big.

If you just use the mkBigCoreTup, mkBigCoreVarTupTy, mkTupleSelector and mkTupleCase functions to do all your work with tuples you should be fine, and not have to worry about the arity limitation at all.

mkChunkifiedSource

Arguments

:: ([a] -> a)

"Small" constructor function, of maximum input arity mAX_TUPLE_SIZE

-> [a]

Possible "big" list of things to construct from

-> a

Constructed thing made possible by recursive decomposition

Lifts a "small" constructor into a "big" constructor by recursive decompositon

Constructing small tuples

mkCoreVarTup :: [Id] -> CoreExprSource

Build a small tuple holding the specified variables

mkCoreVarTupTy :: [Id] -> TypeSource

Bulid the type of a small tuple that holds the specified variables

mkCoreTup :: [CoreExpr] -> CoreExprSource

Build a small tuple holding the specified expressions

Constructing big tuples

mkBigCoreVarTup :: [Id] -> CoreExprSource

Build a big tuple holding the specified variables

mkBigCoreVarTupTy :: [Id] -> TypeSource

Build the type of a big tuple that holds the specified variables

mkBigCoreTup :: [CoreExpr] -> CoreExprSource

Build a big tuple holding the specified expressions

mkBigCoreTupTy :: [Type] -> TypeSource

Build the type of a big tuple that holds the specified type of thing

Deconstructing small tuples

mkSmallTupleSelector :: [Id] -> Id -> Id -> CoreExpr -> CoreExprSource

Like mkTupleSelector but for tuples that are guaranteed never to be "big".

 mkSmallTupleSelector [x] x v e = [| e |]
 mkSmallTupleSelector [x,y,z] x v e = [| case e of v { (x,y,z) -> x } |]

mkSmallTupleCaseSource

Arguments

:: [Id]

The tuple args

-> CoreExpr

Body of the case

-> Id

A variable of the same type as the scrutinee

-> CoreExpr

Scrutinee

-> CoreExpr 

As mkTupleCase, but for a tuple that is small enough to be guaranteed not to need nesting.

Deconstructing big tuples

mkTupleSelectorSource

Arguments

:: [Id]

The Ids to pattern match the tuple against

-> Id

The Id to select

-> Id

A variable of the same type as the scrutinee

-> CoreExpr

Scrutinee

-> CoreExpr

Selector expression

Builds a selector which scrutises the given expression and extracts the one name from the list given. If you want the no-shadowing rule to apply, the caller is responsible for making sure that none of these names are in scope.

If there is just one Id in the tuple, then the selector is just the identity.

If necessary, we pattern match on a "big" tuple.

mkTupleCaseSource

Arguments

:: UniqSupply

For inventing names of intermediate variables

-> [Id]

The tuple identifiers to pattern match on

-> CoreExpr

Body of the case

-> Id

A variable of the same type as the scrutinee

-> CoreExpr

Scrutinee

-> CoreExpr 

A generalization of mkTupleSelector, allowing the body of the case to be an arbitrary expression.

To avoid shadowing, we use uniques to invent new variables.

If necessary we pattern match on a "big" tuple.

Constructing list expressions

mkNilExpr :: Type -> CoreExprSource

Makes a list [] for lists of the specified type

mkConsExpr :: Type -> CoreExpr -> CoreExpr -> CoreExprSource

Makes a list (:) for lists of the specified type

mkListExpr :: Type -> [CoreExpr] -> CoreExprSource

Make a list containing the given expressions, where the list has the given type

mkFoldrExprSource

Arguments

:: MonadThings m 
=> Type

Element type of the list

-> Type

Fold result type

-> CoreExpr

Cons function expression for the fold

-> CoreExpr

Nil expression for the fold

-> CoreExpr

List expression being folded acress

-> m CoreExpr 

Make a fully applied foldr expression

mkBuildExprSource

Arguments

:: (MonadThings m, MonadUnique m) 
=> Type

Type of list elements to be built

-> ((Id, Type) -> (Id, Type) -> m CoreExpr)

Function that, given information about the Ids of the binders for the build worker function, returns the body of that worker

-> m CoreExpr 

Make a build expression applied to a locally-bound worker function

Error Ids