Safe Haskell | None |
---|---|
Language | Haskell98 |
Handy functions for creating much Core syntax
- mkCoreLet :: CoreBind -> CoreExpr -> CoreExpr
- mkCoreLets :: [CoreBind] -> CoreExpr -> CoreExpr
- mkCoreApp :: 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
- 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
- mkFloatExpr :: Float -> CoreExpr
- mkDoubleExpr :: Double -> CoreExpr
- mkCharExpr :: Char -> CoreExpr
- mkStringExpr :: MonadThings m => String -> m CoreExpr
- mkStringExprFS :: MonadThings m => FastString -> m CoreExpr
- data FloatBind
- wrapFloat :: FloatBind -> CoreExpr -> CoreExpr
- mkEqBox :: Coercion -> CoreExpr
- mkChunkified :: ([a] -> a) -> [a] -> a
- mkCoreVarTup :: [Id] -> CoreExpr
- mkCoreVarTupTy :: [Id] -> Type
- mkCoreTup :: [CoreExpr] -> CoreExpr
- 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
- mkRuntimeErrorApp :: Id -> Type -> String -> CoreExpr
- mkImpossibleExpr :: Type -> CoreExpr
- errorIds :: [Id]
- rEC_CON_ERROR_ID :: Id
- iRREFUT_PAT_ERROR_ID :: Id
- rUNTIME_ERROR_ID :: Id
- nON_EXHAUSTIVE_GUARDS_ERROR_ID :: Id
- nO_METHOD_BINDING_ERROR_ID :: Id
- pAT_ERROR_ID :: Id
- eRROR_ID :: Id
- rEC_SEL_ERROR_ID :: Id
- aBSENT_ERROR_ID :: Id
- uNDEFINED_ID :: Id
- undefinedName :: Name
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 :: CoreExpr -> CoreExpr -> CoreExpr infixl 4 Source
Construct an expression which represents the application of one expression to the other
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
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
castBottomExpr :: CoreExpr -> Type -> CoreExpr 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
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
Constructing equality evidence boxes
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.
:: ([a] -> a) | "Small" constructor function, of maximum input arity |
-> [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] -> CoreExpr Source
Build a small tuple holding the specified variables
mkCoreVarTupTy :: [Id] -> Type Source
Bulid the type of a small tuple that holds the specified variables
Constructing big tuples
mkBigCoreVarTup :: [Id] -> CoreExpr Source
Build a big tuple holding the specified variables
mkBigCoreVarTupTy :: [Id] -> Type Source
Build the type of a big tuple that holds the specified variables
mkBigCoreTup :: [CoreExpr] -> CoreExpr Source
Build a big tuple holding the specified expressions
mkBigCoreTupTy :: [Type] -> Type Source
Build the type of a big tuple that holds the specified type of thing
Deconstructing small tuples
mkSmallTupleSelector :: [Id] -> Id -> Id -> CoreExpr -> CoreExpr Source
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 } |]
:: [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
:: [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.
:: 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
:: 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
:: (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
Error Ids
mkImpossibleExpr :: Type -> CoreExpr Source
pAT_ERROR_ID :: Id Source
uNDEFINED_ID :: Id Source