Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- mkWwBodies :: DynFlags -> FamInstEnvs -> VarSet -> Id -> [Demand] -> CprResult -> UniqSM (Maybe WwResult)
- mkWWstr :: DynFlags -> FamInstEnvs -> Bool -> [Var] -> UniqSM (Bool, [Var], CoreExpr -> CoreExpr, CoreExpr -> CoreExpr)
- mkWorkerArgs :: DynFlags -> [Var] -> Type -> ([Var], [Var])
- data DataConAppContext = DataConAppContext {
- dcac_dc :: !DataCon
- dcac_tys :: ![Type]
- dcac_arg_tys :: ![(Scaled Type, StrictnessMark)]
- dcac_co :: !Coercion
- deepSplitProductType_maybe :: FamInstEnvs -> Type -> Maybe DataConAppContext
- wantToUnbox :: FamInstEnvs -> Bool -> Type -> Demand -> Maybe ([Demand], DataConAppContext)
- findTypeShape :: FamInstEnvs -> Type -> TypeShape
- isWorkerSmallEnough :: DynFlags -> Int -> [Var] -> Bool
Documentation
mkWwBodies :: DynFlags -> FamInstEnvs -> VarSet -> Id -> [Demand] -> CprResult -> UniqSM (Maybe WwResult) Source #
mkWWstr :: DynFlags -> FamInstEnvs -> Bool -> [Var] -> UniqSM (Bool, [Var], CoreExpr -> CoreExpr, CoreExpr -> CoreExpr) Source #
data DataConAppContext Source #
Context for a DataCon
application with a hole for every field, including
surrounding coercions.
The result of deepSplitProductType_maybe
and deepSplitCprType_maybe
.
Example:
DataConAppContext Just [Int] [(Lazy, Int)] (co :: Maybe Int ~ First Int)
represents
Just @Int (_1 :: Int) |> co :: First Int
where _1 is a hole for the first argument. The number of arguments is
determined by the length of arg_tys
.
DataConAppContext | |
|
wantToUnbox :: FamInstEnvs -> Bool -> Type -> Demand -> Maybe ([Demand], DataConAppContext) Source #
findTypeShape :: FamInstEnvs -> Type -> TypeShape Source #