ghc-lib-parser-9.6.1.20230312: The GHC API, decoupled from GHC versions
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Core.Make

Description

Handy functions for creating much Core syntax

Synopsis

Constructing normal syntax

mkCoreLet :: CoreBind -> CoreExpr -> CoreExpr Source #

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

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

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

mkCoreApp infixl 4 Source #

Arguments

:: SDoc 
-> CoreExpr

function

-> CoreExpr

argument

-> CoreExpr 

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

mkCoreApps infixl 4 Source #

Arguments

:: CoreExpr

function

-> [CoreExpr]

arguments

-> CoreExpr 

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

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

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

mkWildCase Source #

Arguments

:: CoreExpr

scrutinee

-> Scaled Type 
-> Type

res_ty

-> [CoreAlt]

alts

-> CoreExpr 

Make a case expression whose case binder is unused The alts and res_ty should not have any occurrences of WildId

mkIfThenElse Source #

Arguments

:: CoreExpr

guard

-> CoreExpr

then

-> CoreExpr

else

-> CoreExpr 

mkWildValBinder :: Mult -> Type -> Id Source #

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 GHC.Core.Opt.Simplify.Env

sortQuantVars :: [Var] -> [Var] Source #

Sort the variables, putting type and covars first, in scoped order, and then other Ids

It is a deterministic sort, meaning it doesn't look at the values of Uniques. For explanation why it's important See Note [Unique Determinism] in GHC.Types.Unique.

Constructing boxed literals

mkWordExpr :: Platform -> Integer -> CoreExpr Source #

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

mkIntExpr :: Platform -> Integer -> CoreExpr Source #

Create a CoreExpr which will evaluate to the given Int

mkIntExprInt :: Platform -> Int -> CoreExpr Source #

Create a CoreExpr which will evaluate to the given Int

mkUncheckedIntExpr :: Integer -> CoreExpr Source #

Create a CoreExpr which will evaluate to the given Int. Don't check that the number is in the range of the target platform Int

mkIntegerExpr :: Platform -> Integer -> CoreExpr Source #

Create a CoreExpr which will evaluate to the given Integer

mkNaturalExpr :: Platform -> Integer -> CoreExpr Source #

Create a CoreExpr which will evaluate to the given Natural

mkFloatExpr :: Float -> CoreExpr Source #

Create a CoreExpr which will evaluate to the given Float

mkDoubleExpr :: Double -> CoreExpr Source #

Create a CoreExpr which will evaluate to the given Double

mkCharExpr :: Char -> CoreExpr Source #

Create a CoreExpr which will evaluate to the given Char

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

Create a CoreExpr which will evaluate to the given String

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

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

Floats

data FloatBind Source #

Instances

Instances details
Outputable FloatBind Source # 
Instance details

Defined in GHC.Core.Make

Methods

ppr :: FloatBind -> SDoc Source #

wrapFloats :: [FloatBind] -> CoreExpr -> CoreExpr Source #

Applies the floats from right to left. That is wrapFloats [b1, b2, …, bn] u = let b1 in let b2 in … in let bn in u

Constructing small tuples

mkCoreVarTupTy :: [Id] -> Type Source #

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

mkCoreTup :: [CoreExpr] -> CoreExpr Source #

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

mkCoreUnboxedTuple :: [CoreExpr] -> CoreExpr Source #

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

mkCoreUnboxedSum :: Int -> Int -> [Type] -> CoreExpr -> CoreExpr Source #

Build an unboxed sum.

Alternative number ("alt") starts from 1.

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

Make a core tuple of the given boxity; don't flatten 1-tuples

unitExpr :: CoreExpr Source #

The unit expression

Constructing big tuples

mkChunkified Source #

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 decomposition

chunkify :: [a] -> [[a]] Source #

Split a list into lists that are small enough to have a corresponding tuple arity. The sub-lists of the result all have length <= mAX_TUPLE_SIZE But there may be more than mAX_TUPLE_SIZE sub-lists

mkBigCoreVarTup :: [Id] -> CoreExpr Source #

Build a big tuple holding the specified variables One-tuples are flattened; see Note [Flattening one-tuples] Arguments don't have to have kind Type

mkBigCoreVarTupTy :: [Id] -> Type Source #

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

mkBigCoreTupTy :: [Type] -> Type Source #

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

mkBigCoreTup :: [CoreExpr] -> CoreExpr Source #

Build a "big" tuple holding the specified expressions One-tuples are flattened; see Note [Flattening one-tuples] Arguments don't have to have kind Type; ones that do not are boxed This function crashes (in wrapBox) if given a non-Type argument that it doesn't know how to box.

Deconstructing big tuples

mkBigTupleSelector Source #

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

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

Builds a selector which scrutinises 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.

A tuple selector is not linear in its argument. Consequently, the case expression built by mkBigTupleSelector must consume its scrutinee Many times. And all the argument variables must have multiplicity Many.

mkBigTupleSelectorSolo Source #

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 scrutinises 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.

A tuple selector is not linear in its argument. Consequently, the case expression built by mkBigTupleSelector must consume its scrutinee Many times. And all the argument variables must have multiplicity Many.

mkBigTupleCase Source #

Arguments

:: UniqSupply

For inventing names of intermediate variables

-> [Id]

The tuple identifiers to pattern match on; Bring these into scope in the body

-> CoreExpr

Body of the case

-> CoreExpr

Scrutinee

-> CoreExpr 

A generalization of mkBigTupleSelector, 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 Source #

Makes a list [] for lists of the specified type

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

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

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

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

mkFoldrExpr Source #

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

Arguments

:: (MonadFail m, 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 Source #

Makes a Nothing for the specified type

mkJustExpr :: Type -> CoreExpr -> CoreExpr Source #

Makes a Just from a value of the specified type

Error Ids