ghc-9.0.1: The GHC API
Safe HaskellNone
LanguageHaskell2010

GHC.Types.Demand

Synopsis

Documentation

data StrDmd Source #

Vanilla strictness domain

Instances

Instances details
Eq StrDmd # 
Instance details

Defined in GHC.Types.Demand

Methods

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

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

Show StrDmd # 
Instance details

Defined in GHC.Types.Demand

Outputable StrDmd # 
Instance details

Defined in GHC.Types.Demand

Binary StrDmd # 
Instance details

Defined in GHC.Types.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 # 
Instance details

Defined in GHC.Types.Demand

Methods

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

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

Show UseDmd # 
Instance details

Defined in GHC.Types.Demand

Outputable UseDmd # 
Instance details

Defined in GHC.Types.Demand

Binary UseDmd # 
Instance details

Defined in GHC.Types.Demand

data Count Source #

Abstract counting of usages

Instances

Instances details
Eq Count # 
Instance details

Defined in GHC.Types.Demand

Methods

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

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

Show Count # 
Instance details

Defined in GHC.Types.Demand

Outputable Count # 
Instance details

Defined in GHC.Types.Demand

Binary Count # 
Instance details

Defined in GHC.Types.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 #

Instances

Instances details
Eq DmdType # 
Instance details

Defined in GHC.Types.Demand

Methods

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

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

Outputable DmdType # 
Instance details

Defined in GHC.Types.Demand

Binary DmdType # 
Instance details

Defined in GHC.Types.Demand

lubDmdType :: DmdType -> DmdType -> DmdType Source #

Compute the least upper bound of two DmdTypes elicited /by the same incoming demand/!

nopDmdType :: DmdType Source #

The demand type of doing nothing (lazy, absent, no Divergence information). Note that it is 'not' the top of the lattice (which would be "may use everything"), so it is (no longer) called topDmdType. (SG: I agree, but why is it still topDmd then?)

data Divergence Source #

Divergence lattice. Models a subset lattice of the following exhaustive set of divergence results:

n
nontermination (e.g. loops)
i
throws imprecise exception
p
throws precise exception
c
converges (reduces to WHNF)

The different lattice elements correspond to different subsets, indicated by juxtaposition of indicators (e.g. nc definitely doesn't throw an exception, and may or may not reduce to WHNF).

            Dunno (nipc)
                 |
           ExnOrDiv (nip)
                 |
           Diverges (ni)

As you can see, we don't distinguish n and i. See Note [Precise exceptions and strictness analysis] for why p is so special compared to i.

Constructors

Diverges

Definitely throws an imprecise exception or diverges.

ExnOrDiv

Definitely throws a *precise* exception, an imprecise exception or diverges. Never converges, hence isDeadEndDiv! See scenario 1 in Note [Precise exceptions and strictness analysis].

Dunno

Might diverge, throw any kind of exception or converge.

Instances

Instances details
Eq Divergence # 
Instance details

Defined in GHC.Types.Demand

Show Divergence # 
Instance details

Defined in GHC.Types.Demand

Outputable Divergence # 
Instance details

Defined in GHC.Types.Demand

Binary Divergence # 
Instance details

Defined in GHC.Types.Demand

isDeadEndDiv :: Divergence -> Bool Source #

True if the result indicates that evaluation will not return. See Note [Dead ends].

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

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

isDeadEndSig :: StrictSig -> Bool Source #

True if the signature diverges or throws an exception in a saturated call. See Note [Dead ends].

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 # 
Instance details

Defined in GHC.Types.Demand

Outputable StrictSig # 
Instance details

Defined in GHC.Types.Demand

Binary StrictSig # 
Instance details

Defined in GHC.Types.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]

prependArgsStrictSig :: Int -> StrictSig -> StrictSig Source #

Add extra (topDmd) arguments to a strictness signature. In contrast to etaConvertStrictSig, this prepends additional argument demands. This is used by FloatOut.

etaConvertStrictSig :: Arity -> StrictSig -> StrictSig Source #

We are expanding (x y. e) to (x y z. e z) or reducing from the latter to the former (when the Simplifier identifies a new join points, for example). In contrast to prependArgsStrictSig, this appends extra arg demands if necessary. This works by looking at the DmdType (which was produced under a call demand for the old arity) and trying to transfer as many facts as we can to the call demand of new arity. An arity increase (resulting in a stronger incoming demand) can retain much of the info, while an arity decrease (a weakening of the incoming demand) must fall back to a conservative default.

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

deferAfterPreciseException :: DmdType -> DmdType Source #

When e is evaluated after executing an IO action that may throw a precise exception, we act as if there is an additional control flow path that is taken if e throws a precise exception. The demand type of this control flow path * is lazy and absent (topDmd) in all free variables and arguments * has exnDiv Divergence result So we can simply take a variant of nopDmdType, exnDmdType. Why not nopDmdType? Because then the result of e can never be exnDiv! That means failure to drop dead-ends, see #18086. See Note [Precise exceptions and strictness analysis]

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 # 
Instance details

Defined in GHC.Types.Demand

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