ghc-8.8.1: The GHC API
Safe HaskellNone
LanguageHaskell2010

Demand

Synopsis

Documentation

data StrDmd Source #

Vanilla strictness domain

Instances

Instances details
Eq StrDmd # 
Instance details

Defined in Demand

Methods

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

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

Show StrDmd # 
Instance details

Defined in Demand

Outputable StrDmd # 
Instance details

Defined in Demand

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

Defined in Demand

Methods

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

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

Show UseDmd # 
Instance details

Defined in Demand

Outputable UseDmd # 
Instance details

Defined in Demand

Binary UseDmd # 
Instance details

Defined in Demand

data Count Source #

Abstract counting of usages

Instances

Instances details
Eq Count # 
Instance details

Defined in Demand

Methods

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

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

Show Count # 
Instance details

Defined in Demand

Outputable Count # 
Instance details

Defined in Demand

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

Defined in Demand

Methods

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

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

Outputable DmdType # 
Instance details

Defined in Demand

Binary DmdType # 
Instance details

Defined in Demand

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

type DmdResult = Termination CPRResult Source #

data CPRResult Source #

Instances

Instances details
Eq CPRResult # 
Instance details

Defined in Demand

Show CPRResult # 
Instance details

Defined in Demand

Outputable CPRResult # 
Instance details

Defined in Demand

Binary CPRResult # 
Instance details

Defined in Demand

Binary DmdResult # 
Instance details

Defined in Demand

newtype StrictSig Source #

Constructors

StrictSig DmdType 

Instances

Instances details
Eq StrictSig # 
Instance details

Defined in Demand

Outputable StrictSig # 
Instance details

Defined in Demand

Binary StrictSig # 
Instance details

Defined in Demand

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

data TypeShape Source #

Instances

Instances details
Outputable TypeShape # 
Instance details

Defined in 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