ghc-8.10.2: The GHC API
Safe HaskellNone
LanguageHaskell2010

Demand

Synopsis

Documentation

data StrDmd Source #

Vanilla strictness domain

Instances

Instances details
Eq StrDmd Source # 
Instance details

Defined in Demand

Methods

(==) :: StrDmd -> StrDmd -> Bool #

(/=) :: StrDmd -> StrDmd -> Bool #

Show StrDmd Source # 
Instance details

Defined in Demand

Outputable StrDmd Source # 
Instance details

Defined in Demand

Binary StrDmd Source # 
Instance details

Defined in Demand

data UseDmd Source #

Domain for genuine usage

Constructors

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. For product types, UHead is equivalent to U(AAA); see mkUProd.

UHead is needed only to express the demand of seq and 'case' which are polymorphic; i.e. the scrutinised value is of type a rather than a product type. That's why we can't use UProd [A,A,A]

Since (UCall _ Abs) is ill-typed, UHead doesn't make sense for lambdas

Used

May be used and its sub-components may be used. (top of the lattice)

Instances

Instances details
Eq UseDmd Source # 
Instance details

Defined in Demand

Methods

(==) :: UseDmd -> UseDmd -> Bool #

(/=) :: UseDmd -> UseDmd -> Bool #

Show UseDmd Source # 
Instance details

Defined in Demand

Outputable UseDmd Source # 
Instance details

Defined in Demand

Binary UseDmd Source # 
Instance details

Defined in Demand

data Count Source #

Abstract counting of usages

Instances

Instances details
Eq Count Source # 
Instance details

Defined in Demand

Methods

(==) :: Count -> Count -> Bool #

(/=) :: Count -> Count -> Bool #

Show Count Source # 
Instance details

Defined in Demand

Methods

showsPrec :: Int -> Count -> ShowS #

show :: Count -> String #

showList :: [Count] -> ShowS #

Outputable Count Source # 
Instance details

Defined in Demand

Binary Count Source # 
Instance details

Defined in Demand

type Demand = JointDmd ArgStr ArgUse Source #

type DmdShell = JointDmd (Str ()) (Use ()) Source #

type CleanDemand = JointDmd StrDmd UseDmd Source #

getStrDmd :: JointDmd s u -> s Source #

getUseDmd :: JointDmd s u -> u Source #

oneifyDmd :: JointDmd s (Use u) -> JointDmd s (Use u) Source #

isAbsDmd :: JointDmd (Str s) (Use u) -> Bool Source #

data DmdType Source #

Constructors

DmdType DmdEnv [Demand] DmdResult 

Instances

Instances details
Eq DmdType Source # 
Instance details

Defined in Demand

Methods

(==) :: DmdType -> DmdType -> Bool #

(/=) :: DmdType -> DmdType -> Bool #

Outputable DmdType Source # 
Instance details

Defined in Demand

Binary DmdType Source # 
Instance details

Defined in Demand

ensureArgs :: Arity -> DmdType -> DmdType Source #

This makes sure we can use the demand type with n arguments. It extends the argument list with the correct resTypeArgDmd. It also adjusts the DmdResult: Divergence survives additional arguments, CPR information does not (and definite converge also would not).

type BothDmdArg = (DmdEnv, Termination ()) Source #

type DmdResult = Termination CPRResult Source #

data CPRResult Source #

Instances

Instances details
Eq CPRResult Source # 
Instance details

Defined in Demand

Show CPRResult Source # 
Instance details

Defined in Demand

Outputable CPRResult Source # 
Instance details

Defined in Demand

Binary CPRResult Source # 
Instance details

Defined in Demand

Binary DmdResult Source # 
Instance details

Defined in Demand

isBotRes :: DmdResult -> Bool Source #

True if the result diverges or throws an exception

appIsBottom :: StrictSig -> Int -> Bool Source #

Returns true if an application to n args would diverge or throw an exception See Note [Unsaturated applications]

isBottomingSig :: StrictSig -> Bool Source #

True if the signature diverges or throws an exception

newtype StrictSig Source #

The depth of the wrapped DmdType encodes the arity at which it is safe to unleash. Better construct this through mkStrictSigForArity. See Note [Understanding DmdType and StrictSig]

Constructors

StrictSig DmdType 

Instances

Instances details
Eq StrictSig Source # 
Instance details

Defined in Demand

Outputable StrictSig Source # 
Instance details

Defined in Demand

Binary StrictSig Source # 
Instance details

Defined in Demand

mkStrictSigForArity :: Arity -> DmdType -> StrictSig Source #

Turns a DmdType computed for the particular Arity into a StrictSig unleashable at that arity. See Note [Understanding DmdType and StrictSig]

increaseStrictSigArity :: Int -> StrictSig -> StrictSig Source #

Add extra arguments to a strictness signature. In contrast to etaExpandStrictSig, this prepends additional argument demands and leaves CPR info intact.

etaExpandStrictSig :: Arity -> StrictSig -> StrictSig Source #

We are expanding (x y. e) to (x y z. e z). In contrast to increaseStrictSigArity, this appends extra arg demands if necessary, potentially destroying the signature's CPR property.

isStrictDmd :: JointDmd (Str s) (Use u) -> Bool Source #

mkCallDmd :: CleanDemand -> CleanDemand Source #

Wraps the CleanDemand with a one-shot call demand: d -> C1(d).

mkCallDmds :: Arity -> CleanDemand -> CleanDemand Source #

mkCallDmds n d returns C1(C1...(C1 d)) where there are n C1's.

data TypeShape Source #

Instances

Instances details
Outputable TypeShape Source # 
Instance details

Defined in Demand

peelTsFuns :: Arity -> TypeShape -> Maybe TypeShape Source #

peelTsFuns n ts tries to peel off n TsFun constructors from ts and returns Just the wrapped TypeShape on success, and Nothing otherwise.

useCount :: Use u -> Count Source #

isUsedOnce :: JointDmd (Str s) (Use u) -> Bool 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