| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
MkCore
Contents
Description
Handy functions for creating much Core syntax
Synopsis
- mkCoreLet :: CoreBind -> CoreExpr -> CoreExpr
- mkCoreLets :: [CoreBind] -> CoreExpr -> CoreExpr
- mkCoreApp :: SDoc -> CoreExpr -> CoreExpr -> CoreExpr
- mkCoreApps :: CoreExpr -> [CoreExpr] -> CoreExpr
- mkCoreConApps :: DataCon -> [CoreExpr] -> CoreExpr
- mkCoreLams :: [CoreBndr] -> CoreExpr -> CoreExpr
- mkWildCase :: CoreExpr -> Type -> Type -> [CoreAlt] -> CoreExpr
- mkIfThenElse :: CoreExpr -> CoreExpr -> CoreExpr -> CoreExpr
- mkWildValBinder :: Type -> Id
- mkWildEvBinder :: PredType -> EvVar
- mkSingleAltCase :: CoreExpr -> Id -> AltCon -> [Var] -> CoreExpr -> CoreExpr
- sortQuantVars :: [Var] -> [Var]
- castBottomExpr :: CoreExpr -> Type -> CoreExpr
- mkWordExpr :: DynFlags -> Integer -> CoreExpr
- mkWordExprWord :: DynFlags -> Word -> CoreExpr
- mkIntExpr :: DynFlags -> Integer -> CoreExpr
- mkIntExprInt :: DynFlags -> Int -> CoreExpr
- mkIntegerExpr :: MonadThings m => Integer -> m CoreExpr
- mkNaturalExpr :: 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
- mkStringExprFSWith :: Monad m => (Name -> m Id) -> FastString -> m CoreExpr
- data FloatBind
- wrapFloat :: FloatBind -> CoreExpr -> CoreExpr
- wrapFloats :: [FloatBind] -> CoreExpr -> CoreExpr
- floatBindings :: FloatBind -> [Var]
- mkCoreVarTup :: [Id] -> CoreExpr
- mkCoreVarTupTy :: [Id] -> Type
- mkCoreTup :: [CoreExpr] -> CoreExpr
- mkCoreUbxTup :: [Type] -> [CoreExpr] -> CoreExpr
- mkCoreTupBoxity :: Boxity -> [CoreExpr] -> CoreExpr
- unitExpr :: CoreExpr
- mkBigCoreVarTup :: [Id] -> CoreExpr
- mkBigCoreVarTup1 :: [Id] -> CoreExpr
- mkBigCoreVarTupTy :: [Id] -> Type
- mkBigCoreTupTy :: [Type] -> Type
- mkBigCoreTup :: [CoreExpr] -> CoreExpr
- mkSmallTupleSelector :: [Id] -> Id -> Id -> CoreExpr -> CoreExpr
- mkSmallTupleCase :: [Id] -> CoreExpr -> Id -> CoreExpr -> CoreExpr
- mkTupleSelector :: [Id] -> Id -> Id -> CoreExpr -> CoreExpr
- mkTupleSelector1 :: [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 :: (MonadFail m, MonadThings m, MonadUnique m) => Type -> ((Id, Type) -> (Id, Type) -> m CoreExpr) -> m CoreExpr
- mkNothingExpr :: Type -> CoreExpr
- mkJustExpr :: Type -> CoreExpr -> CoreExpr
- mkRuntimeErrorApp :: Id -> Type -> String -> CoreExpr
- mkImpossibleExpr :: Type -> CoreExpr
- mkAbsentErrorApp :: Type -> String -> CoreExpr
- errorIds :: [Id]
- rEC_CON_ERROR_ID :: Id
- rUNTIME_ERROR_ID :: Id
- nON_EXHAUSTIVE_GUARDS_ERROR_ID :: Id
- nO_METHOD_BINDING_ERROR_ID :: Id
- pAT_ERROR_ID :: Id
- rEC_SEL_ERROR_ID :: Id
- aBSENT_ERROR_ID :: Id
- tYPE_ERROR_ID :: Id
- aBSENT_SUM_FIELD_ERROR_ID :: Id
Constructing normal syntax
mkCoreLet :: CoreBind -> CoreExpr -> CoreExpr Source #
Bind a binding group over an expression, using a let or case as
 appropriate (see CoreSyn)
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 :: SDoc -> CoreExpr -> CoreExpr -> CoreExpr infixl 4 Source #
Construct an expression which represents the application of one expression to the other Respects the let/app invariant by building a case expression where necessary See CoreSyn Note [CoreSyn let/app invariant]
mkCoreApps :: CoreExpr -> [CoreExpr] -> CoreExpr infixl 4 Source #
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 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
mkWildValBinder :: 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 SimplEnv
mkWildEvBinder :: PredType -> EvVar Source #
sortQuantVars :: [Var] -> [Var] Source #
Constructing boxed literals
mkWordExpr :: DynFlags -> Integer -> CoreExpr Source #
Create a CoreExpr which will evaluate to the a Word with the given value
mkWordExprWord :: DynFlags -> Word -> CoreExpr Source #
Create a CoreExpr which will evaluate to the given Word
mkIntExpr :: DynFlags -> Integer -> CoreExpr Source #
Create a CoreExpr which will evaluate to the given Int
mkIntExprInt :: DynFlags -> Int -> CoreExpr Source #
Create a CoreExpr which will evaluate to the given Int
mkIntegerExpr :: MonadThings m => Integer -> m CoreExpr Source #
Create a CoreExpr which will evaluate to the given Integer
mkNaturalExpr :: MonadThings m => Integer -> m CoreExpr Source #
Create a CoreExpr which will evaluate to the given Natural
mkDoubleExpr :: Double -> CoreExpr Source #
Create a CoreExpr which will evaluate to the given Double
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
mkStringExprFSWith :: Monad m => (Name -> m Id) -> FastString -> m CoreExpr Source #
Floats
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
floatBindings :: FloatBind -> [Var] Source #
Constructing small tuples
mkCoreVarTup :: [Id] -> CoreExpr Source #
Build a small tuple holding the specified variables One-tuples are flattened; see Note [Flattening one-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]
mkCoreUbxTup :: [Type] -> [CoreExpr] -> CoreExpr Source #
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]
Constructing big tuples
mkBigCoreVarTup :: [Id] -> CoreExpr Source #
Build a big tuple holding the specified variables One-tuples are flattened; see Note [Flattening one-tuples]
mkBigCoreVarTup1 :: [Id] -> CoreExpr Source #
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]
Deconstructing small tuples
mkSmallTupleSelector :: [Id] -> Id -> Id -> CoreExpr -> CoreExpr Source #
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 } |]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
Arguments
| :: [Id] | The  | 
| -> Id | The  | 
| -> 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.
Arguments
| :: [Id] | The  | 
| -> Id | The  | 
| -> 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.
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
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
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
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  | 
| -> 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
Error Ids
mkImpossibleExpr :: Type -> CoreExpr Source #
pAT_ERROR_ID :: Id Source #
aBSENT_ERROR_ID :: Id Source #
tYPE_ERROR_ID :: Id Source #