ghc-9.6.0.20230302: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Types.Cpr

Description

Types for the Constructed Product Result lattice. GHC.Core.Opt.CprAnal and GHC.Core.Opt.WorkWrap.Utils are its primary customers via idCprSig.

Synopsis

Documentation

data Cpr where Source #

Bundled Patterns

pattern ConCpr :: ConTag -> [Cpr] -> Cpr 

Instances

Instances details
Binary Cpr Source # 
Instance details

Defined in GHC.Types.Cpr

Methods

put_ :: BinHandle -> Cpr -> IO () Source #

put :: BinHandle -> Cpr -> IO (Bin Cpr) Source #

get :: BinHandle -> IO Cpr Source #

Outputable Cpr Source #

BNF:

cpr ::= ''                               -- TopCpr
     |  n                                -- FlatConCpr n
     |  n '(' cpr1 ',' cpr2 ',' ... ')'  -- ConCpr n [cpr1,cpr2,...]
     |  'b'                              -- BotCpr

Examples: * `f x = f x` has result CPR b * `1(1,)` is a valid (nested) Cpr denotation for `(I# 42#, f 42)`.

Instance details

Defined in GHC.Types.Cpr

Methods

ppr :: Cpr -> SDoc Source #

Eq Cpr Source # 
Instance details

Defined in GHC.Types.Cpr

Methods

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

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

data CprType Source #

The abstract domain \(A_t\) from the original 'CPR for Haskell' paper.

Constructors

CprType 

Fields

Instances

Instances details
Binary CprType Source # 
Instance details

Defined in GHC.Types.Cpr

Outputable CprType Source #

BNF:

cpr_ty ::= cpr               -- short form if arty == 0
        |  '\' arty '.' cpr  -- if arty > 0

Examples: * `f x y z = f x y z` has denotation `3.b` * `g !x = (x+1, x+2)` has denotation `1.1(1,1)`.

Instance details

Defined in GHC.Types.Cpr

Methods

ppr :: CprType -> SDoc Source #

Eq CprType Source # 
Instance details

Defined in GHC.Types.Cpr

Methods

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

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

unpackConFieldsCpr :: DataCon -> Cpr -> UnpackConFieldsResult Source #

Unpacks a ConCpr-shaped Cpr and returns the field Cprs wrapped in a ForeachField. Otherwise, it returns AllFieldsSame with the appropriate Cpr to assume for each field.

The use of UnpackConFieldsResult allows O(1) space for the common, non-ConCpr case.

newtype CprSig Source #

The arity of the wrapped CprType is the arity at which it is safe to unleash. See Note [Understanding DmdType and DmdSig] in GHC.Types.Demand

Constructors

CprSig 

Fields

Instances

Instances details
Binary CprSig Source # 
Instance details

Defined in GHC.Types.Cpr

Outputable CprSig Source #

Only print the CPR result

Instance details

Defined in GHC.Types.Cpr

Methods

ppr :: CprSig -> SDoc Source #

Eq CprSig Source # 
Instance details

Defined in GHC.Types.Cpr

Methods

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

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

mkCprSigForArity :: Arity -> CprType -> CprSig Source #

Turns a CprType computed for the particular Arity into a CprSig unleashable at that arity. See Note [Understanding DmdType and DmdSig] in GHC.Types.Demand

prependArgsCprSig :: Arity -> CprSig -> CprSig Source #

Add extra value args to CprSig