ghc-6.10.2: The GHC APIContentsIndex
MkCore
Contents
Constructing normal syntax
Constructing boxed literals
Constructing general big tuples
Constructing small tuples
Constructing big tuples
Deconstructing small tuples
Deconstructing big tuples
Constructing list expressions
Description
Handy functions for creating much Core syntax
Synopsis
mkCoreLet :: CoreBind -> CoreExpr -> CoreExpr
mkCoreLets :: [CoreBind] -> CoreExpr -> CoreExpr
mkCoreApp :: CoreExpr -> CoreExpr -> CoreExpr
mkCoreApps :: CoreExpr -> [CoreExpr] -> CoreExpr
mkCoreConApps :: DataCon -> [CoreExpr] -> CoreExpr
mkCoreLams :: [CoreBndr] -> CoreExpr -> CoreExpr
mkWordExpr :: Integer -> CoreExpr
mkWordExprWord :: Word -> CoreExpr
mkIntExpr :: Integer -> CoreExpr
mkIntExprInt :: Int -> CoreExpr
mkIntegerExpr :: MonadThings m => Integer -> m CoreExpr
mkFloatExpr :: Float -> CoreExpr
mkDoubleExpr :: Double -> CoreExpr
mkCharExpr :: Char -> CoreExpr
mkStringExpr :: MonadThings m => String -> m CoreExpr
mkStringExprFS :: MonadThings m => FastString -> m CoreExpr
mkChunkified :: ([a] -> a) -> [a] -> a
mkCoreVarTup :: [Id] -> CoreExpr
mkCoreVarTupTy :: [Id] -> Type
mkCoreTup :: [CoreExpr] -> CoreExpr
mkCoreTupTy :: [Type] -> Type
mkBigCoreVarTup :: [Id] -> CoreExpr
mkBigCoreVarTupTy :: [Id] -> Type
mkBigCoreTup :: [CoreExpr] -> CoreExpr
mkBigCoreTupTy :: [Type] -> Type
mkSmallTupleSelector :: [Id] -> Id -> Id -> CoreExpr -> CoreExpr
mkSmallTupleCase :: [Id] -> CoreExpr -> Id -> CoreExpr -> CoreExpr
mkTupleSelector :: [Id] -> Id -> Id -> CoreExpr -> CoreExpr
mkTupleCase :: UniqSupply -> [Id] -> CoreExpr -> Id -> CoreExpr -> CoreExpr
mkNilExpr :: Type -> CoreExpr
mkConsExpr :: Type -> CoreExpr -> CoreExpr -> CoreExpr
mkListExpr :: Type -> [CoreExpr] -> CoreExpr
mkFoldrExpr :: MonadThings m => Type -> Type -> CoreExpr -> CoreExpr -> CoreExpr -> m CoreExpr
mkBuildExpr :: (MonadThings m, MonadUnique m) => Type -> ((Id, Type) -> (Id, Type) -> m CoreExpr) -> m CoreExpr
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 :: CoreExpr -> CoreExpr -> CoreExpr
Construct an expression which represents the application of one expression to the other
mkCoreApps :: CoreExpr -> [CoreExpr] -> 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
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
Constructing boxed literals
mkWordExpr :: Integer -> CoreExpr
Create a CoreExpr which will evaluate to the a Word with the given value
mkWordExprWord :: Word -> CoreExpr
Create a CoreExpr which will evaluate to the given Word
mkIntExpr :: Integer -> CoreExpr
Create a CoreExpr which will evaluate to the given Int
mkIntExprInt :: 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
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.

mkChunkified
::
=> [a] -> a"Small" constructor function, of maximum input arity mAX_TUPLE_SIZE
-> [a]Possible "big" list of things to construct from
-> aConstructed thing made possible by recursive decomposition
Lifts a "small" constructor into a "big" constructor by recursive decompositon
Constructing small tuples
mkCoreVarTup :: [Id] -> CoreExpr
Build a small tuple holding the specified variables
mkCoreVarTupTy :: [Id] -> Type
Bulid the type of a small tuple that holds the specified variables
mkCoreTup :: [CoreExpr] -> CoreExpr
Build a small tuple holding the specified expressions
mkCoreTupTy :: [Type] -> Type
Build the type of a small tuple that holds the specified type of thing
Constructing big tuples
mkBigCoreVarTup :: [Id] -> CoreExpr
Build a big tuple holding the specified variables
mkBigCoreVarTupTy :: [Id] -> Type
Build the type of a big tuple that holds the specified variables
mkBigCoreTup :: [CoreExpr] -> CoreExpr
Build a big tuple holding the specified expressions
mkBigCoreTupTy :: [Type] -> Type
Build the type of a big tuple that holds the specified type of thing
Deconstructing small tuples
mkSmallTupleSelector :: [Id] -> Id -> Id -> CoreExpr -> CoreExpr

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
:: [Id]The tuple args
-> CoreExprBody of the case
-> IdA variable of the same type as the scrutinee
-> CoreExprScrutinee
-> CoreExpr
As mkTupleCase, but for a tuple that is small enough to be guaranteed not to need nesting.
Deconstructing big tuples
mkTupleSelector
:: [Id]The Ids to pattern match the tuple against
-> IdThe Id to select
-> IdA variable of the same type as the scrutinee
-> CoreExprScrutinee
-> CoreExprSelector 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
:: UniqSupplyFor inventing names of intermediate variables
-> [Id]The tuple identifiers to pattern match on
-> CoreExprBody of the case
-> IdA variable of the same type as the scrutinee
-> CoreExprScrutinee
-> 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
:: MonadThings m
=> TypeElement type of the list
-> TypeFold result type
-> CoreExprCons function expression for the fold
-> CoreExprNil expression for the fold
-> CoreExprList expression being folded acress
-> m CoreExpr
Make a fully applied foldr expression
mkBuildExpr
:: (MonadThings m, MonadUnique m)
=> TypeType of list elements to be built
-> (Id, Type) -> (Id, Type) -> m CoreExprFunction 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
Produced by Haddock version 2.4.2