Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data StrDmd
- data UseDmd
- data Count
- type Demand = JointDmd ArgStr ArgUse
- type CleanDemand = JointDmd StrDmd UseDmd
- getStrDmd :: JointDmd s u -> s
- getUseDmd :: JointDmd s u -> u
- mkProdDmd :: [Demand] -> CleanDemand
- mkOnceUsedDmd :: CleanDemand -> Demand
- mkManyUsedDmd :: CleanDemand -> Demand
- mkHeadStrict :: CleanDemand -> CleanDemand
- oneifyDmd :: Demand -> Demand
- toCleanDmd :: Demand -> Type -> (DmdShell, CleanDemand)
- absDmd :: Demand
- topDmd :: Demand
- botDmd :: Demand
- seqDmd :: Demand
- lubDmd :: Demand -> Demand -> Demand
- bothDmd :: Demand -> Demand -> Demand
- lazyApply1Dmd :: Demand
- lazyApply2Dmd :: Demand
- strictApply1Dmd :: Demand
- catchArgDmd :: Demand
- isTopDmd :: Demand -> Bool
- isAbsDmd :: Demand -> Bool
- isSeqDmd :: Demand -> Bool
- peelUseCall :: UseDmd -> Maybe (Count, UseDmd)
- cleanUseDmd_maybe :: Demand -> Maybe UseDmd
- strictenDmd :: Demand -> CleanDemand
- bothCleanDmd :: CleanDemand -> CleanDemand -> CleanDemand
- addCaseBndrDmd :: Demand -> [Demand] -> [Demand]
- data DmdType = DmdType DmdEnv [Demand] DmdResult
- dmdTypeDepth :: DmdType -> Arity
- lubDmdType :: DmdType -> DmdType -> DmdType
- bothDmdType :: DmdType -> BothDmdArg -> DmdType
- nopDmdType :: DmdType
- botDmdType :: DmdType
- mkDmdType :: DmdEnv -> [Demand] -> DmdResult -> DmdType
- addDemand :: Demand -> DmdType -> DmdType
- removeDmdTyArgs :: DmdType -> DmdType
- type BothDmdArg = (DmdEnv, Termination ())
- mkBothDmdArg :: DmdEnv -> BothDmdArg
- toBothDmdArg :: DmdType -> BothDmdArg
- type DmdEnv = VarEnv Demand
- emptyDmdEnv :: VarEnv Demand
- peelFV :: DmdType -> Var -> (DmdType, Demand)
- findIdDemand :: DmdType -> Var -> Demand
- type DmdResult = Termination CPRResult
- data CPRResult
- isBotRes :: DmdResult -> Bool
- isTopRes :: DmdResult -> Bool
- topRes :: DmdResult
- botRes :: DmdResult
- exnRes :: DmdResult
- cprProdRes :: [DmdType] -> DmdResult
- vanillaCprProdRes :: Arity -> DmdResult
- cprSumRes :: ConTag -> DmdResult
- appIsBottom :: StrictSig -> Int -> Bool
- isBottomingSig :: StrictSig -> Bool
- pprIfaceStrictSig :: StrictSig -> SDoc
- trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult
- returnsCPR_maybe :: DmdResult -> Maybe ConTag
- newtype StrictSig = StrictSig DmdType
- mkStrictSig :: DmdType -> StrictSig
- mkClosedStrictSig :: [Demand] -> DmdResult -> StrictSig
- nopSig :: StrictSig
- botSig :: StrictSig
- exnSig :: StrictSig
- cprProdSig :: Arity -> StrictSig
- isTopSig :: StrictSig -> Bool
- hasDemandEnvSig :: StrictSig -> Bool
- splitStrictSig :: StrictSig -> ([Demand], DmdResult)
- strictSigDmdEnv :: StrictSig -> DmdEnv
- increaseStrictSigArity :: Int -> StrictSig -> StrictSig
- etaExpandStrictSig :: Arity -> StrictSig -> StrictSig
- seqDemand :: Demand -> ()
- seqDemandList :: [Demand] -> ()
- seqDmdType :: DmdType -> ()
- seqStrictSig :: StrictSig -> ()
- evalDmd :: Demand
- cleanEvalDmd :: CleanDemand
- cleanEvalProdDmd :: Arity -> CleanDemand
- isStrictDmd :: Demand -> Bool
- splitDmdTy :: DmdType -> (Demand, DmdType)
- splitFVs :: Bool -> DmdEnv -> (DmdEnv, DmdEnv)
- deferAfterIO :: DmdType -> DmdType
- postProcessUnsat :: DmdShell -> DmdType -> DmdType
- postProcessDmdType :: DmdShell -> DmdType -> BothDmdArg
- splitProdDmd_maybe :: Demand -> Maybe [Demand]
- peelCallDmd :: CleanDemand -> (CleanDemand, DmdShell)
- mkCallDmd :: CleanDemand -> CleanDemand
- mkWorkerDemand :: Int -> Demand
- dmdTransformSig :: StrictSig -> CleanDemand -> DmdType
- dmdTransformDataConSig :: Arity -> StrictSig -> CleanDemand -> DmdType
- dmdTransformDictSelSig :: StrictSig -> CleanDemand -> DmdType
- argOneShots :: Demand -> [OneShotInfo]
- argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]]
- saturatedByOneShots :: Int -> Demand -> Bool
- trimToType :: Demand -> TypeShape -> Demand
- data TypeShape
- useCount :: Use u -> Count
- isUsedOnce :: Demand -> Bool
- reuseEnv :: DmdEnv -> DmdEnv
- killUsageDemand :: DynFlags -> Demand -> Demand
- killUsageSig :: DynFlags -> StrictSig -> StrictSig
- zapUsageDemand :: Demand -> Demand
- zapUsageEnvSig :: StrictSig -> StrictSig
- zapUsedOnceDemand :: Demand -> Demand
- zapUsedOnceSig :: StrictSig -> StrictSig
- strictifyDictDmd :: Type -> Demand -> Demand
Documentation
Domain for genuine usage
UCall Count UseDmd | Call demand for absence. Used only for values of function type |
UProd [ArgUse] | Product. Used only for values of product type See Note [Don't optimise UProd(Used) to Used] Invariant: Not all components are Abs (in that case, use UHead) |
UHead | May be used but its sub-components are
definitely *not* used. Roughly U(AAA)
e.g. the usage of |
Used | May be used and its sub-components may be used. (top of the lattice) |
type CleanDemand = JointDmd StrDmd UseDmd Source #
mkProdDmd :: [Demand] -> CleanDemand Source #
mkOnceUsedDmd :: CleanDemand -> Demand Source #
mkManyUsedDmd :: CleanDemand -> Demand Source #
toCleanDmd :: Demand -> Type -> (DmdShell, CleanDemand) Source #
catchArgDmd :: Demand Source #
strictenDmd :: Demand -> CleanDemand Source #
bothCleanDmd :: CleanDemand -> CleanDemand -> CleanDemand Source #
dmdTypeDepth :: DmdType -> Arity Source #
bothDmdType :: DmdType -> BothDmdArg -> DmdType Source #
nopDmdType :: DmdType Source #
botDmdType :: DmdType Source #
removeDmdTyArgs :: DmdType -> DmdType Source #
type BothDmdArg = (DmdEnv, Termination ()) Source #
mkBothDmdArg :: DmdEnv -> BothDmdArg Source #
toBothDmdArg :: DmdType -> BothDmdArg Source #
cprProdRes :: [DmdType] -> DmdResult Source #
vanillaCprProdRes :: Arity -> DmdResult Source #
isBottomingSig :: StrictSig -> Bool Source #
pprIfaceStrictSig :: StrictSig -> SDoc Source #
mkStrictSig :: DmdType -> StrictSig Source #
cprProdSig :: Arity -> StrictSig Source #
hasDemandEnvSig :: StrictSig -> Bool Source #
strictSigDmdEnv :: StrictSig -> DmdEnv Source #
seqDemandList :: [Demand] -> () Source #
seqDmdType :: DmdType -> () Source #
seqStrictSig :: StrictSig -> () Source #
cleanEvalProdDmd :: Arity -> CleanDemand Source #
isStrictDmd :: Demand -> Bool Source #
deferAfterIO :: DmdType -> DmdType Source #
postProcessUnsat :: DmdShell -> DmdType -> DmdType Source #
postProcessDmdType :: DmdShell -> DmdType -> BothDmdArg Source #
peelCallDmd :: CleanDemand -> (CleanDemand, DmdShell) Source #
mkCallDmd :: CleanDemand -> CleanDemand Source #
mkWorkerDemand :: Int -> Demand Source #
dmdTransformSig :: StrictSig -> CleanDemand -> DmdType Source #
dmdTransformDataConSig :: Arity -> StrictSig -> CleanDemand -> DmdType Source #
dmdTransformDictSelSig :: StrictSig -> CleanDemand -> DmdType Source #
argOneShots :: Demand -> [OneShotInfo] Source #
argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]] Source #
isUsedOnce :: Demand -> Bool Source #
zapUsageDemand :: Demand -> Demand Source #
zapUsageEnvSig :: StrictSig -> StrictSig Source #
zapUsedOnceDemand :: Demand -> Demand Source #
Remove all 1* information (but not C1 information) from the demand
zapUsedOnceSig :: StrictSig -> StrictSig Source #
Remove all 1* information (but not C1 information) from the strictness signature