ghc-8.0.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

MkCore

Contents

Description

Handy functions for creating much Core syntax

Synopsis

Constructing normal syntax

mkCoreLet :: CoreBind -> CoreExpr -> CoreExpr #

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

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

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

mkCoreApp :: SDoc -> CoreExpr -> CoreExpr -> CoreExpr infixl 4 #

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

mkCoreApps :: CoreExpr -> [CoreExpr] -> CoreExpr infixl 4 #

Construct an expression which represents the application of a number of expressions to another. The leftmost expression in the list is applied first Respects the let/app invariant by building a case expression where necessary See CoreSyn Note [CoreSyn let/app invariant]

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

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 -> CoreExpr #

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 -> Id #

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. See Note [WildCard binders] in SimplEnv

Constructing boxed literals

mkWordExpr :: DynFlags -> Integer -> CoreExpr #

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

mkWordExprWord :: DynFlags -> Word -> CoreExpr #

Create a CoreExpr which will evaluate to the given Word

mkIntExpr :: DynFlags -> Integer -> CoreExpr #

Create a CoreExpr which will evaluate to the given Int

mkIntExprInt :: DynFlags -> Int -> CoreExpr #

Create a CoreExpr which will evaluate to the given Int

mkIntegerExpr :: MonadThings m => Integer -> m CoreExpr #

Create a CoreExpr which will evaluate to the given Integer

mkFloatExpr :: Float -> CoreExpr #

Create a CoreExpr which will evaluate to the given Float

mkDoubleExpr :: Double -> CoreExpr #

Create a CoreExpr which will evaluate to the given Double

mkCharExpr :: Char -> CoreExpr #

Create a CoreExpr which will evaluate to the given Char

mkStringExpr :: MonadThings m => String -> m CoreExpr #

Create a CoreExpr which will evaluate to the given String

mkStringExprFS :: MonadThings m => FastString -> m CoreExpr #

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

Floats

Constructing small tuples

mkCoreVarTup :: [Id] -> CoreExpr #

Build a small tuple holding the specified variables One-tuples are flattened; see Note [Flattening of one-tuples]

mkCoreVarTupTy :: [Id] -> Type #

Bulid the type of a small tuple that holds the specified variables One-tuples are flattened; see Note [Flattening of one-tuples]

mkCoreTup :: [CoreExpr] -> CoreExpr #

Build a small tuple holding the specified expressions One-tuples are flattened; see NOte [Flattening of one-tuples]

mkCoreUbxTup :: [Type] -> [CoreExpr] -> CoreExpr #

Build a small unboxed tuple holding the specified expressions, with the given types. The types must be the types of the expressions. Do not include the RuntimeRep specifiers; this function calculates them for you. Does not flatten one-tuples; see Note [Flattening one-tuples]

mkCoreTupBoxity :: Boxity -> [CoreExpr] -> CoreExpr #

Make a core tuple of the given boxity

Constructing big tuples

mkBigCoreVarTup :: [Id] -> CoreExpr #

Build a big tuple holding the specified variables One-tuples are flattened; see Note [Flattening of one-tuples]

mkBigCoreVarTupTy :: [Id] -> Type #

Build the type of a big tuple that holds the specified variables One-tuples are flattened; see Note [Flattening of one-tuples]

mkBigCoreTupTy :: [Type] -> Type #

Build the type of a big tuple that holds the specified type of thing One-tuples are flattened; see Note [Flattening of one-tuples]

mkBigCoreTup :: [CoreExpr] -> CoreExpr #

Build a big tuple holding the specified expressions One-tuples are flattened; see Note [Flattening of one-tuples]

Deconstructing small tuples

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

mkSmallTupleSelector1 is like mkSmallTupleSelector but one-tuples are NOT flattened (see Note [Flattening one-tuples])

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 } |]

mkSmallTupleCase #

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

mkTupleSelector #

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

mkTupleSelector1 is like mkTupleSelector but one-tuples are NOT flattened (see Note [Flattening one-tuples])

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.

mkTupleSelector1 #

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.

mkTupleCase #

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 -> CoreExpr #

Makes a list [] for lists of the specified type

mkConsExpr :: Type -> CoreExpr -> CoreExpr -> CoreExpr #

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

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

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

mkFoldrExpr #

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

mkBuildExpr #

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

Constructing Maybe expressions

mkNothingExpr :: Type -> CoreExpr #

Makes a Nothing for the specified type

mkJustExpr :: Type -> CoreExpr -> CoreExpr #

Makes a Just from a value of the specified type

Error Ids