{-# LANGUAGE CPP, FlexibleInstances, TypeSynonymInstances, RecordWildCards #-}
module Demand (
StrDmd, UseDmd(..), Count,
Demand, DmdShell, CleanDemand, getStrDmd, getUseDmd,
mkProdDmd, mkOnceUsedDmd, mkManyUsedDmd, mkHeadStrict, oneifyDmd,
toCleanDmd,
absDmd, topDmd, botDmd, seqDmd,
lubDmd, bothDmd,
lazyApply1Dmd, lazyApply2Dmd, strictApply1Dmd,
catchArgDmd,
isTopDmd, isAbsDmd, isSeqDmd,
peelUseCall, cleanUseDmd_maybe, strictenDmd, bothCleanDmd,
addCaseBndrDmd,
DmdType(..), dmdTypeDepth, lubDmdType, bothDmdType,
nopDmdType, botDmdType, mkDmdType,
addDemand, removeDmdTyArgs,
BothDmdArg, mkBothDmdArg, toBothDmdArg,
DmdEnv, emptyDmdEnv,
peelFV, findIdDemand,
DmdResult, CPRResult,
isBotRes, isTopRes,
topRes, botRes, exnRes, cprProdRes,
vanillaCprProdRes, cprSumRes,
appIsBottom, isBottomingSig, pprIfaceStrictSig,
trimCPRInfo, returnsCPR_maybe,
StrictSig(..), mkStrictSig, mkClosedStrictSig,
nopSig, botSig, exnSig, cprProdSig,
isTopSig, hasDemandEnvSig,
splitStrictSig, strictSigDmdEnv,
increaseStrictSigArity, etaExpandStrictSig,
seqDemand, seqDemandList, seqDmdType, seqStrictSig,
evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd,
splitDmdTy, splitFVs,
deferAfterIO,
postProcessUnsat, postProcessDmdType,
splitProdDmd_maybe, peelCallDmd, peelManyCalls, mkCallDmd,
mkWorkerDemand, dmdTransformSig, dmdTransformDataConSig,
dmdTransformDictSelSig, argOneShots, argsOneShots, saturatedByOneShots,
trimToType, TypeShape(..),
useCount, isUsedOnce, reuseEnv,
killUsageDemand, killUsageSig, zapUsageDemand, zapUsageEnvSig,
zapUsedOnceDemand, zapUsedOnceSig,
strictifyDictDmd, strictifyDmd
) where
#include "GhclibHsVersions.h"
import GhcPrelude
import DynFlags
import Outputable
import Var ( Var )
import VarEnv
import UniqFM
import Util
import BasicTypes
import Binary
import Maybes ( orElse )
import Type ( Type )
import TyCon ( isNewTyCon, isClassTyCon )
import DataCon ( splitDataProductType_maybe )
data JointDmd s u = JD { JointDmd s u -> s
sd :: s, JointDmd s u -> u
ud :: u }
deriving ( JointDmd s u -> JointDmd s u -> Bool
(JointDmd s u -> JointDmd s u -> Bool)
-> (JointDmd s u -> JointDmd s u -> Bool) -> Eq (JointDmd s u)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall s u. (Eq s, Eq u) => JointDmd s u -> JointDmd s u -> Bool
/= :: JointDmd s u -> JointDmd s u -> Bool
$c/= :: forall s u. (Eq s, Eq u) => JointDmd s u -> JointDmd s u -> Bool
== :: JointDmd s u -> JointDmd s u -> Bool
$c== :: forall s u. (Eq s, Eq u) => JointDmd s u -> JointDmd s u -> Bool
Eq, Int -> JointDmd s u -> ShowS
[JointDmd s u] -> ShowS
JointDmd s u -> String
(Int -> JointDmd s u -> ShowS)
-> (JointDmd s u -> String)
-> ([JointDmd s u] -> ShowS)
-> Show (JointDmd s u)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall s u. (Show s, Show u) => Int -> JointDmd s u -> ShowS
forall s u. (Show s, Show u) => [JointDmd s u] -> ShowS
forall s u. (Show s, Show u) => JointDmd s u -> String
showList :: [JointDmd s u] -> ShowS
$cshowList :: forall s u. (Show s, Show u) => [JointDmd s u] -> ShowS
show :: JointDmd s u -> String
$cshow :: forall s u. (Show s, Show u) => JointDmd s u -> String
showsPrec :: Int -> JointDmd s u -> ShowS
$cshowsPrec :: forall s u. (Show s, Show u) => Int -> JointDmd s u -> ShowS
Show )
getStrDmd :: JointDmd s u -> s
getStrDmd :: JointDmd s u -> s
getStrDmd = JointDmd s u -> s
forall s u. JointDmd s u -> s
sd
getUseDmd :: JointDmd s u -> u
getUseDmd :: JointDmd s u -> u
getUseDmd = JointDmd s u -> u
forall s u. JointDmd s u -> u
ud
instance (Outputable s, Outputable u) => Outputable (JointDmd s u) where
ppr :: JointDmd s u -> SDoc
ppr (JD {sd :: forall s u. JointDmd s u -> s
sd = s
s, ud :: forall s u. JointDmd s u -> u
ud = u
u}) = SDoc -> SDoc
angleBrackets (s -> SDoc
forall a. Outputable a => a -> SDoc
ppr s
s SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
',' SDoc -> SDoc -> SDoc
<> u -> SDoc
forall a. Outputable a => a -> SDoc
ppr u
u)
mkJointDmd :: s -> u -> JointDmd s u
mkJointDmd :: s -> u -> JointDmd s u
mkJointDmd s
s u
u = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: s
sd = s
s, ud :: u
ud = u
u }
mkJointDmds :: [s] -> [u] -> [JointDmd s u]
mkJointDmds :: [s] -> [u] -> [JointDmd s u]
mkJointDmds [s]
ss [u]
as = String -> (s -> u -> JointDmd s u) -> [s] -> [u] -> [JointDmd s u]
forall a b c. String -> (a -> b -> c) -> [a] -> [b] -> [c]
zipWithEqual String
"mkJointDmds" s -> u -> JointDmd s u
forall s u. s -> u -> JointDmd s u
mkJointDmd [s]
ss [u]
as
data StrDmd
= HyperStr
| SCall StrDmd
| SProd [ArgStr]
| HeadStr
deriving ( StrDmd -> StrDmd -> Bool
(StrDmd -> StrDmd -> Bool)
-> (StrDmd -> StrDmd -> Bool) -> Eq StrDmd
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StrDmd -> StrDmd -> Bool
$c/= :: StrDmd -> StrDmd -> Bool
== :: StrDmd -> StrDmd -> Bool
$c== :: StrDmd -> StrDmd -> Bool
Eq, Int -> StrDmd -> ShowS
[StrDmd] -> ShowS
StrDmd -> String
(Int -> StrDmd -> ShowS)
-> (StrDmd -> String) -> ([StrDmd] -> ShowS) -> Show StrDmd
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StrDmd] -> ShowS
$cshowList :: [StrDmd] -> ShowS
show :: StrDmd -> String
$cshow :: StrDmd -> String
showsPrec :: Int -> StrDmd -> ShowS
$cshowsPrec :: Int -> StrDmd -> ShowS
Show )
type ArgStr = Str StrDmd
data Str s = Lazy
| Str ExnStr s
deriving ( Str s -> Str s -> Bool
(Str s -> Str s -> Bool) -> (Str s -> Str s -> Bool) -> Eq (Str s)
forall s. Eq s => Str s -> Str s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Str s -> Str s -> Bool
$c/= :: forall s. Eq s => Str s -> Str s -> Bool
== :: Str s -> Str s -> Bool
$c== :: forall s. Eq s => Str s -> Str s -> Bool
Eq, Int -> Str s -> ShowS
[Str s] -> ShowS
Str s -> String
(Int -> Str s -> ShowS)
-> (Str s -> String) -> ([Str s] -> ShowS) -> Show (Str s)
forall s. Show s => Int -> Str s -> ShowS
forall s. Show s => [Str s] -> ShowS
forall s. Show s => Str s -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Str s] -> ShowS
$cshowList :: forall s. Show s => [Str s] -> ShowS
show :: Str s -> String
$cshow :: forall s. Show s => Str s -> String
showsPrec :: Int -> Str s -> ShowS
$cshowsPrec :: forall s. Show s => Int -> Str s -> ShowS
Show )
data ExnStr
= VanStr
| ExnStr
deriving( ExnStr -> ExnStr -> Bool
(ExnStr -> ExnStr -> Bool)
-> (ExnStr -> ExnStr -> Bool) -> Eq ExnStr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExnStr -> ExnStr -> Bool
$c/= :: ExnStr -> ExnStr -> Bool
== :: ExnStr -> ExnStr -> Bool
$c== :: ExnStr -> ExnStr -> Bool
Eq, Int -> ExnStr -> ShowS
[ExnStr] -> ShowS
ExnStr -> String
(Int -> ExnStr -> ShowS)
-> (ExnStr -> String) -> ([ExnStr] -> ShowS) -> Show ExnStr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExnStr] -> ShowS
$cshowList :: [ExnStr] -> ShowS
show :: ExnStr -> String
$cshow :: ExnStr -> String
showsPrec :: Int -> ExnStr -> ShowS
$cshowsPrec :: Int -> ExnStr -> ShowS
Show )
strBot, strTop :: ArgStr
strBot :: ArgStr
strBot = ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str ExnStr
VanStr StrDmd
HyperStr
strTop :: ArgStr
strTop = ArgStr
forall s. Str s
Lazy
mkSCall :: StrDmd -> StrDmd
mkSCall :: StrDmd -> StrDmd
mkSCall StrDmd
HyperStr = StrDmd
HyperStr
mkSCall StrDmd
s = StrDmd -> StrDmd
SCall StrDmd
s
mkSProd :: [ArgStr] -> StrDmd
mkSProd :: [ArgStr] -> StrDmd
mkSProd [ArgStr]
sx
| (ArgStr -> Bool) -> [ArgStr] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ArgStr -> Bool
isHyperStr [ArgStr]
sx = StrDmd
HyperStr
| (ArgStr -> Bool) -> [ArgStr] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ArgStr -> Bool
isLazy [ArgStr]
sx = StrDmd
HeadStr
| Bool
otherwise = [ArgStr] -> StrDmd
SProd [ArgStr]
sx
isLazy :: ArgStr -> Bool
isLazy :: ArgStr -> Bool
isLazy ArgStr
Lazy = Bool
True
isLazy (Str {}) = Bool
False
isHyperStr :: ArgStr -> Bool
isHyperStr :: ArgStr -> Bool
isHyperStr (Str ExnStr
_ StrDmd
HyperStr) = Bool
True
isHyperStr ArgStr
_ = Bool
False
instance Outputable StrDmd where
ppr :: StrDmd -> SDoc
ppr StrDmd
HyperStr = Char -> SDoc
char Char
'B'
ppr (SCall StrDmd
s) = Char -> SDoc
char Char
'C' SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
parens (StrDmd -> SDoc
forall a. Outputable a => a -> SDoc
ppr StrDmd
s)
ppr StrDmd
HeadStr = Char -> SDoc
char Char
'S'
ppr (SProd [ArgStr]
sx) = Char -> SDoc
char Char
'S' SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
parens ([SDoc] -> SDoc
hcat ((ArgStr -> SDoc) -> [ArgStr] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map ArgStr -> SDoc
forall a. Outputable a => a -> SDoc
ppr [ArgStr]
sx))
instance Outputable ArgStr where
ppr :: ArgStr -> SDoc
ppr (Str ExnStr
x StrDmd
s) = (case ExnStr
x of ExnStr
VanStr -> SDoc
empty; ExnStr
ExnStr -> Char -> SDoc
char Char
'x')
SDoc -> SDoc -> SDoc
<> StrDmd -> SDoc
forall a. Outputable a => a -> SDoc
ppr StrDmd
s
ppr ArgStr
Lazy = Char -> SDoc
char Char
'L'
lubArgStr :: ArgStr -> ArgStr -> ArgStr
lubArgStr :: ArgStr -> ArgStr -> ArgStr
lubArgStr ArgStr
Lazy ArgStr
_ = ArgStr
forall s. Str s
Lazy
lubArgStr ArgStr
_ ArgStr
Lazy = ArgStr
forall s. Str s
Lazy
lubArgStr (Str ExnStr
x1 StrDmd
s1) (Str ExnStr
x2 StrDmd
s2) = ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str (ExnStr
x1 ExnStr -> ExnStr -> ExnStr
`lubExnStr` ExnStr
x2) (StrDmd
s1 StrDmd -> StrDmd -> StrDmd
`lubStr` StrDmd
s2)
lubExnStr :: ExnStr -> ExnStr -> ExnStr
lubExnStr :: ExnStr -> ExnStr -> ExnStr
lubExnStr ExnStr
VanStr ExnStr
VanStr = ExnStr
VanStr
lubExnStr ExnStr
_ ExnStr
_ = ExnStr
ExnStr
lubStr :: StrDmd -> StrDmd -> StrDmd
lubStr :: StrDmd -> StrDmd -> StrDmd
lubStr StrDmd
HyperStr StrDmd
s = StrDmd
s
lubStr (SCall StrDmd
s1) StrDmd
HyperStr = StrDmd -> StrDmd
SCall StrDmd
s1
lubStr (SCall StrDmd
_) StrDmd
HeadStr = StrDmd
HeadStr
lubStr (SCall StrDmd
s1) (SCall StrDmd
s2) = StrDmd -> StrDmd
SCall (StrDmd
s1 StrDmd -> StrDmd -> StrDmd
`lubStr` StrDmd
s2)
lubStr (SCall StrDmd
_) (SProd [ArgStr]
_) = StrDmd
HeadStr
lubStr (SProd [ArgStr]
sx) StrDmd
HyperStr = [ArgStr] -> StrDmd
SProd [ArgStr]
sx
lubStr (SProd [ArgStr]
_) StrDmd
HeadStr = StrDmd
HeadStr
lubStr (SProd [ArgStr]
s1) (SProd [ArgStr]
s2)
| [ArgStr]
s1 [ArgStr] -> [ArgStr] -> Bool
forall a b. [a] -> [b] -> Bool
`equalLength` [ArgStr]
s2 = [ArgStr] -> StrDmd
mkSProd ((ArgStr -> ArgStr -> ArgStr) -> [ArgStr] -> [ArgStr] -> [ArgStr]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ArgStr -> ArgStr -> ArgStr
lubArgStr [ArgStr]
s1 [ArgStr]
s2)
| Bool
otherwise = StrDmd
HeadStr
lubStr (SProd [ArgStr]
_) (SCall StrDmd
_) = StrDmd
HeadStr
lubStr StrDmd
HeadStr StrDmd
_ = StrDmd
HeadStr
bothArgStr :: ArgStr -> ArgStr -> ArgStr
bothArgStr :: ArgStr -> ArgStr -> ArgStr
bothArgStr ArgStr
Lazy ArgStr
s = ArgStr
s
bothArgStr ArgStr
s ArgStr
Lazy = ArgStr
s
bothArgStr (Str ExnStr
x1 StrDmd
s1) (Str ExnStr
x2 StrDmd
s2) = ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str (ExnStr
x1 ExnStr -> ExnStr -> ExnStr
`bothExnStr` ExnStr
x2) (StrDmd
s1 StrDmd -> StrDmd -> StrDmd
`bothStr` StrDmd
s2)
bothExnStr :: ExnStr -> ExnStr -> ExnStr
bothExnStr :: ExnStr -> ExnStr -> ExnStr
bothExnStr ExnStr
ExnStr ExnStr
ExnStr = ExnStr
ExnStr
bothExnStr ExnStr
_ ExnStr
_ = ExnStr
VanStr
bothStr :: StrDmd -> StrDmd -> StrDmd
bothStr :: StrDmd -> StrDmd -> StrDmd
bothStr StrDmd
HyperStr StrDmd
_ = StrDmd
HyperStr
bothStr StrDmd
HeadStr StrDmd
s = StrDmd
s
bothStr (SCall StrDmd
_) StrDmd
HyperStr = StrDmd
HyperStr
bothStr (SCall StrDmd
s1) StrDmd
HeadStr = StrDmd -> StrDmd
SCall StrDmd
s1
bothStr (SCall StrDmd
s1) (SCall StrDmd
s2) = StrDmd -> StrDmd
SCall (StrDmd
s1 StrDmd -> StrDmd -> StrDmd
`bothStr` StrDmd
s2)
bothStr (SCall StrDmd
_) (SProd [ArgStr]
_) = StrDmd
HyperStr
bothStr (SProd [ArgStr]
_) StrDmd
HyperStr = StrDmd
HyperStr
bothStr (SProd [ArgStr]
s1) StrDmd
HeadStr = [ArgStr] -> StrDmd
SProd [ArgStr]
s1
bothStr (SProd [ArgStr]
s1) (SProd [ArgStr]
s2)
| [ArgStr]
s1 [ArgStr] -> [ArgStr] -> Bool
forall a b. [a] -> [b] -> Bool
`equalLength` [ArgStr]
s2 = [ArgStr] -> StrDmd
mkSProd ((ArgStr -> ArgStr -> ArgStr) -> [ArgStr] -> [ArgStr] -> [ArgStr]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ArgStr -> ArgStr -> ArgStr
bothArgStr [ArgStr]
s1 [ArgStr]
s2)
| Bool
otherwise = StrDmd
HyperStr
bothStr (SProd [ArgStr]
_) (SCall StrDmd
_) = StrDmd
HyperStr
seqStrDmd :: StrDmd -> ()
seqStrDmd :: StrDmd -> ()
seqStrDmd (SProd [ArgStr]
ds) = [ArgStr] -> ()
seqStrDmdList [ArgStr]
ds
seqStrDmd (SCall StrDmd
s) = StrDmd -> ()
seqStrDmd StrDmd
s
seqStrDmd StrDmd
_ = ()
seqStrDmdList :: [ArgStr] -> ()
seqStrDmdList :: [ArgStr] -> ()
seqStrDmdList [] = ()
seqStrDmdList (ArgStr
d:[ArgStr]
ds) = ArgStr -> ()
seqArgStr ArgStr
d () -> () -> ()
`seq` [ArgStr] -> ()
seqStrDmdList [ArgStr]
ds
seqArgStr :: ArgStr -> ()
seqArgStr :: ArgStr -> ()
seqArgStr ArgStr
Lazy = ()
seqArgStr (Str ExnStr
x StrDmd
s) = ExnStr
x ExnStr -> () -> ()
`seq` StrDmd -> ()
seqStrDmd StrDmd
s
splitArgStrProdDmd :: Int -> ArgStr -> Maybe [ArgStr]
splitArgStrProdDmd :: Int -> ArgStr -> Maybe [ArgStr]
splitArgStrProdDmd Int
n ArgStr
Lazy = [ArgStr] -> Maybe [ArgStr]
forall a. a -> Maybe a
Just (Int -> ArgStr -> [ArgStr]
forall a. Int -> a -> [a]
replicate Int
n ArgStr
forall s. Str s
Lazy)
splitArgStrProdDmd Int
n (Str ExnStr
_ StrDmd
s) = Int -> StrDmd -> Maybe [ArgStr]
splitStrProdDmd Int
n StrDmd
s
splitStrProdDmd :: Int -> StrDmd -> Maybe [ArgStr]
splitStrProdDmd :: Int -> StrDmd -> Maybe [ArgStr]
splitStrProdDmd Int
n StrDmd
HyperStr = [ArgStr] -> Maybe [ArgStr]
forall a. a -> Maybe a
Just (Int -> ArgStr -> [ArgStr]
forall a. Int -> a -> [a]
replicate Int
n ArgStr
strBot)
splitStrProdDmd Int
n StrDmd
HeadStr = [ArgStr] -> Maybe [ArgStr]
forall a. a -> Maybe a
Just (Int -> ArgStr -> [ArgStr]
forall a. Int -> a -> [a]
replicate Int
n ArgStr
strTop)
splitStrProdDmd Int
n (SProd [ArgStr]
ds) = WARN( not (ds `lengthIs` n),
text "splitStrProdDmd" $$ ppr n $$ ppr ds )
[ArgStr] -> Maybe [ArgStr]
forall a. a -> Maybe a
Just [ArgStr]
ds
splitStrProdDmd Int
_ (SCall {}) = Maybe [ArgStr]
forall a. Maybe a
Nothing
data UseDmd
= UCall Count UseDmd
| UProd [ArgUse]
| UHead
| Used
deriving ( UseDmd -> UseDmd -> Bool
(UseDmd -> UseDmd -> Bool)
-> (UseDmd -> UseDmd -> Bool) -> Eq UseDmd
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UseDmd -> UseDmd -> Bool
$c/= :: UseDmd -> UseDmd -> Bool
== :: UseDmd -> UseDmd -> Bool
$c== :: UseDmd -> UseDmd -> Bool
Eq, Int -> UseDmd -> ShowS
[UseDmd] -> ShowS
UseDmd -> String
(Int -> UseDmd -> ShowS)
-> (UseDmd -> String) -> ([UseDmd] -> ShowS) -> Show UseDmd
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UseDmd] -> ShowS
$cshowList :: [UseDmd] -> ShowS
show :: UseDmd -> String
$cshow :: UseDmd -> String
showsPrec :: Int -> UseDmd -> ShowS
$cshowsPrec :: Int -> UseDmd -> ShowS
Show )
type ArgUse = Use UseDmd
data Use u
= Abs
| Use Count u
deriving ( Use u -> Use u -> Bool
(Use u -> Use u -> Bool) -> (Use u -> Use u -> Bool) -> Eq (Use u)
forall u. Eq u => Use u -> Use u -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Use u -> Use u -> Bool
$c/= :: forall u. Eq u => Use u -> Use u -> Bool
== :: Use u -> Use u -> Bool
$c== :: forall u. Eq u => Use u -> Use u -> Bool
Eq, Int -> Use u -> ShowS
[Use u] -> ShowS
Use u -> String
(Int -> Use u -> ShowS)
-> (Use u -> String) -> ([Use u] -> ShowS) -> Show (Use u)
forall u. Show u => Int -> Use u -> ShowS
forall u. Show u => [Use u] -> ShowS
forall u. Show u => Use u -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Use u] -> ShowS
$cshowList :: forall u. Show u => [Use u] -> ShowS
show :: Use u -> String
$cshow :: forall u. Show u => Use u -> String
showsPrec :: Int -> Use u -> ShowS
$cshowsPrec :: forall u. Show u => Int -> Use u -> ShowS
Show )
data Count = One | Many
deriving ( Count -> Count -> Bool
(Count -> Count -> Bool) -> (Count -> Count -> Bool) -> Eq Count
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Count -> Count -> Bool
$c/= :: Count -> Count -> Bool
== :: Count -> Count -> Bool
$c== :: Count -> Count -> Bool
Eq, Int -> Count -> ShowS
[Count] -> ShowS
Count -> String
(Int -> Count -> ShowS)
-> (Count -> String) -> ([Count] -> ShowS) -> Show Count
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Count] -> ShowS
$cshowList :: [Count] -> ShowS
show :: Count -> String
$cshow :: Count -> String
showsPrec :: Int -> Count -> ShowS
$cshowsPrec :: Int -> Count -> ShowS
Show )
instance Outputable ArgUse where
ppr :: ArgUse -> SDoc
ppr ArgUse
Abs = Char -> SDoc
char Char
'A'
ppr (Use Count
Many UseDmd
a) = UseDmd -> SDoc
forall a. Outputable a => a -> SDoc
ppr UseDmd
a
ppr (Use Count
One UseDmd
a) = Char -> SDoc
char Char
'1' SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'*' SDoc -> SDoc -> SDoc
<> UseDmd -> SDoc
forall a. Outputable a => a -> SDoc
ppr UseDmd
a
instance Outputable UseDmd where
ppr :: UseDmd -> SDoc
ppr UseDmd
Used = Char -> SDoc
char Char
'U'
ppr (UCall Count
c UseDmd
a) = Char -> SDoc
char Char
'C' SDoc -> SDoc -> SDoc
<> Count -> SDoc
forall a. Outputable a => a -> SDoc
ppr Count
c SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
parens (UseDmd -> SDoc
forall a. Outputable a => a -> SDoc
ppr UseDmd
a)
ppr UseDmd
UHead = Char -> SDoc
char Char
'H'
ppr (UProd [ArgUse]
as) = Char -> SDoc
char Char
'U' SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
parens ([SDoc] -> SDoc
hcat (SDoc -> [SDoc] -> [SDoc]
punctuate (Char -> SDoc
char Char
',') ((ArgUse -> SDoc) -> [ArgUse] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map ArgUse -> SDoc
forall a. Outputable a => a -> SDoc
ppr [ArgUse]
as)))
instance Outputable Count where
ppr :: Count -> SDoc
ppr Count
One = Char -> SDoc
char Char
'1'
ppr Count
Many = String -> SDoc
text String
""
useBot, useTop :: ArgUse
useBot :: ArgUse
useBot = ArgUse
forall u. Use u
Abs
useTop :: ArgUse
useTop = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
Many UseDmd
Used
mkUCall :: Count -> UseDmd -> UseDmd
mkUCall :: Count -> UseDmd -> UseDmd
mkUCall Count
c UseDmd
a = Count -> UseDmd -> UseDmd
UCall Count
c UseDmd
a
mkUProd :: [ArgUse] -> UseDmd
mkUProd :: [ArgUse] -> UseDmd
mkUProd [ArgUse]
ux
| (ArgUse -> Bool) -> [ArgUse] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (ArgUse -> ArgUse -> Bool
forall a. Eq a => a -> a -> Bool
== ArgUse
forall u. Use u
Abs) [ArgUse]
ux = UseDmd
UHead
| Bool
otherwise = [ArgUse] -> UseDmd
UProd [ArgUse]
ux
lubCount :: Count -> Count -> Count
lubCount :: Count -> Count -> Count
lubCount Count
_ Count
Many = Count
Many
lubCount Count
Many Count
_ = Count
Many
lubCount Count
x Count
_ = Count
x
lubArgUse :: ArgUse -> ArgUse -> ArgUse
lubArgUse :: ArgUse -> ArgUse -> ArgUse
lubArgUse ArgUse
Abs ArgUse
x = ArgUse
x
lubArgUse ArgUse
x ArgUse
Abs = ArgUse
x
lubArgUse (Use Count
c1 UseDmd
a1) (Use Count
c2 UseDmd
a2) = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use (Count -> Count -> Count
lubCount Count
c1 Count
c2) (UseDmd -> UseDmd -> UseDmd
lubUse UseDmd
a1 UseDmd
a2)
lubUse :: UseDmd -> UseDmd -> UseDmd
lubUse :: UseDmd -> UseDmd -> UseDmd
lubUse UseDmd
UHead UseDmd
u = UseDmd
u
lubUse (UCall Count
c UseDmd
u) UseDmd
UHead = Count -> UseDmd -> UseDmd
UCall Count
c UseDmd
u
lubUse (UCall Count
c1 UseDmd
u1) (UCall Count
c2 UseDmd
u2) = Count -> UseDmd -> UseDmd
UCall (Count -> Count -> Count
lubCount Count
c1 Count
c2) (UseDmd -> UseDmd -> UseDmd
lubUse UseDmd
u1 UseDmd
u2)
lubUse (UCall Count
_ UseDmd
_) UseDmd
_ = UseDmd
Used
lubUse (UProd [ArgUse]
ux) UseDmd
UHead = [ArgUse] -> UseDmd
UProd [ArgUse]
ux
lubUse (UProd [ArgUse]
ux1) (UProd [ArgUse]
ux2)
| [ArgUse]
ux1 [ArgUse] -> [ArgUse] -> Bool
forall a b. [a] -> [b] -> Bool
`equalLength` [ArgUse]
ux2 = [ArgUse] -> UseDmd
UProd ([ArgUse] -> UseDmd) -> [ArgUse] -> UseDmd
forall a b. (a -> b) -> a -> b
$ (ArgUse -> ArgUse -> ArgUse) -> [ArgUse] -> [ArgUse] -> [ArgUse]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ArgUse -> ArgUse -> ArgUse
lubArgUse [ArgUse]
ux1 [ArgUse]
ux2
| Bool
otherwise = UseDmd
Used
lubUse (UProd {}) (UCall {}) = UseDmd
Used
lubUse (UProd [ArgUse]
ux) UseDmd
Used = [ArgUse] -> UseDmd
UProd ((ArgUse -> ArgUse) -> [ArgUse] -> [ArgUse]
forall a b. (a -> b) -> [a] -> [b]
map (ArgUse -> ArgUse -> ArgUse
`lubArgUse` ArgUse
useTop) [ArgUse]
ux)
lubUse UseDmd
Used (UProd [ArgUse]
ux) = [ArgUse] -> UseDmd
UProd ((ArgUse -> ArgUse) -> [ArgUse] -> [ArgUse]
forall a b. (a -> b) -> [a] -> [b]
map (ArgUse -> ArgUse -> ArgUse
`lubArgUse` ArgUse
useTop) [ArgUse]
ux)
lubUse UseDmd
Used UseDmd
_ = UseDmd
Used
bothArgUse :: ArgUse -> ArgUse -> ArgUse
bothArgUse :: ArgUse -> ArgUse -> ArgUse
bothArgUse ArgUse
Abs ArgUse
x = ArgUse
x
bothArgUse ArgUse
x ArgUse
Abs = ArgUse
x
bothArgUse (Use Count
_ UseDmd
a1) (Use Count
_ UseDmd
a2) = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
Many (UseDmd -> UseDmd -> UseDmd
bothUse UseDmd
a1 UseDmd
a2)
bothUse :: UseDmd -> UseDmd -> UseDmd
bothUse :: UseDmd -> UseDmd -> UseDmd
bothUse UseDmd
UHead UseDmd
u = UseDmd
u
bothUse (UCall Count
c UseDmd
u) UseDmd
UHead = Count -> UseDmd -> UseDmd
UCall Count
c UseDmd
u
bothUse (UCall Count
_ UseDmd
u1) (UCall Count
_ UseDmd
u2) = Count -> UseDmd -> UseDmd
UCall Count
Many (UseDmd
u1 UseDmd -> UseDmd -> UseDmd
`lubUse` UseDmd
u2)
bothUse (UCall {}) UseDmd
_ = UseDmd
Used
bothUse (UProd [ArgUse]
ux) UseDmd
UHead = [ArgUse] -> UseDmd
UProd [ArgUse]
ux
bothUse (UProd [ArgUse]
ux1) (UProd [ArgUse]
ux2)
| [ArgUse]
ux1 [ArgUse] -> [ArgUse] -> Bool
forall a b. [a] -> [b] -> Bool
`equalLength` [ArgUse]
ux2 = [ArgUse] -> UseDmd
UProd ([ArgUse] -> UseDmd) -> [ArgUse] -> UseDmd
forall a b. (a -> b) -> a -> b
$ (ArgUse -> ArgUse -> ArgUse) -> [ArgUse] -> [ArgUse] -> [ArgUse]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ArgUse -> ArgUse -> ArgUse
bothArgUse [ArgUse]
ux1 [ArgUse]
ux2
| Bool
otherwise = UseDmd
Used
bothUse (UProd {}) (UCall {}) = UseDmd
Used
bothUse UseDmd
Used (UProd [ArgUse]
ux) = [ArgUse] -> UseDmd
UProd ((ArgUse -> ArgUse) -> [ArgUse] -> [ArgUse]
forall a b. (a -> b) -> [a] -> [b]
map (ArgUse -> ArgUse -> ArgUse
`bothArgUse` ArgUse
useTop) [ArgUse]
ux)
bothUse (UProd [ArgUse]
ux) UseDmd
Used = [ArgUse] -> UseDmd
UProd ((ArgUse -> ArgUse) -> [ArgUse] -> [ArgUse]
forall a b. (a -> b) -> [a] -> [b]
map (ArgUse -> ArgUse -> ArgUse
`bothArgUse` ArgUse
useTop) [ArgUse]
ux)
bothUse UseDmd
Used UseDmd
_ = UseDmd
Used
peelUseCall :: UseDmd -> Maybe (Count, UseDmd)
peelUseCall :: UseDmd -> Maybe (Count, UseDmd)
peelUseCall (UCall Count
c UseDmd
u) = (Count, UseDmd) -> Maybe (Count, UseDmd)
forall a. a -> Maybe a
Just (Count
c,UseDmd
u)
peelUseCall UseDmd
_ = Maybe (Count, UseDmd)
forall a. Maybe a
Nothing
addCaseBndrDmd :: Demand
-> [Demand]
-> [Demand]
addCaseBndrDmd :: Demand -> [Demand] -> [Demand]
addCaseBndrDmd (JD { sd :: forall s u. JointDmd s u -> s
sd = ArgStr
ms, ud :: forall s u. JointDmd s u -> u
ud = ArgUse
mu }) [Demand]
alt_dmds
= case ArgUse
mu of
ArgUse
Abs -> [Demand]
alt_dmds
Use Count
_ UseDmd
u -> (Demand -> Demand -> Demand) -> [Demand] -> [Demand] -> [Demand]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Demand -> Demand -> Demand
bothDmd [Demand]
alt_dmds ([ArgStr] -> [ArgUse] -> [Demand]
forall s u. [s] -> [u] -> [JointDmd s u]
mkJointDmds [ArgStr]
ss [ArgUse]
us)
where
Just [ArgStr]
ss = Int -> ArgStr -> Maybe [ArgStr]
splitArgStrProdDmd Int
arity ArgStr
ms
Just [ArgUse]
us = Int -> UseDmd -> Maybe [ArgUse]
splitUseProdDmd Int
arity UseDmd
u
where
arity :: Int
arity = [Demand] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Demand]
alt_dmds
markReusedDmd :: ArgUse -> ArgUse
markReusedDmd :: ArgUse -> ArgUse
markReusedDmd ArgUse
Abs = ArgUse
forall u. Use u
Abs
markReusedDmd (Use Count
_ UseDmd
a) = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
Many (UseDmd -> UseDmd
markReused UseDmd
a)
markReused :: UseDmd -> UseDmd
markReused :: UseDmd -> UseDmd
markReused (UCall Count
_ UseDmd
u) = Count -> UseDmd -> UseDmd
UCall Count
Many UseDmd
u
markReused (UProd [ArgUse]
ux) = [ArgUse] -> UseDmd
UProd ((ArgUse -> ArgUse) -> [ArgUse] -> [ArgUse]
forall a b. (a -> b) -> [a] -> [b]
map ArgUse -> ArgUse
markReusedDmd [ArgUse]
ux)
markReused UseDmd
u = UseDmd
u
isUsedMU :: ArgUse -> Bool
isUsedMU :: ArgUse -> Bool
isUsedMU ArgUse
Abs = Bool
True
isUsedMU (Use Count
One UseDmd
_) = Bool
False
isUsedMU (Use Count
Many UseDmd
u) = UseDmd -> Bool
isUsedU UseDmd
u
isUsedU :: UseDmd -> Bool
isUsedU :: UseDmd -> Bool
isUsedU UseDmd
Used = Bool
True
isUsedU UseDmd
UHead = Bool
True
isUsedU (UProd [ArgUse]
us) = (ArgUse -> Bool) -> [ArgUse] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ArgUse -> Bool
isUsedMU [ArgUse]
us
isUsedU (UCall Count
One UseDmd
_) = Bool
False
isUsedU (UCall Count
Many UseDmd
_) = Bool
True
seqUseDmd :: UseDmd -> ()
seqUseDmd :: UseDmd -> ()
seqUseDmd (UProd [ArgUse]
ds) = [ArgUse] -> ()
seqArgUseList [ArgUse]
ds
seqUseDmd (UCall Count
c UseDmd
d) = Count
c Count -> () -> ()
`seq` UseDmd -> ()
seqUseDmd UseDmd
d
seqUseDmd UseDmd
_ = ()
seqArgUseList :: [ArgUse] -> ()
seqArgUseList :: [ArgUse] -> ()
seqArgUseList [] = ()
seqArgUseList (ArgUse
d:[ArgUse]
ds) = ArgUse -> ()
seqArgUse ArgUse
d () -> () -> ()
`seq` [ArgUse] -> ()
seqArgUseList [ArgUse]
ds
seqArgUse :: ArgUse -> ()
seqArgUse :: ArgUse -> ()
seqArgUse (Use Count
c UseDmd
u) = Count
c Count -> () -> ()
`seq` UseDmd -> ()
seqUseDmd UseDmd
u
seqArgUse ArgUse
_ = ()
splitUseProdDmd :: Int -> UseDmd -> Maybe [ArgUse]
splitUseProdDmd :: Int -> UseDmd -> Maybe [ArgUse]
splitUseProdDmd Int
n UseDmd
Used = [ArgUse] -> Maybe [ArgUse]
forall a. a -> Maybe a
Just (Int -> ArgUse -> [ArgUse]
forall a. Int -> a -> [a]
replicate Int
n ArgUse
useTop)
splitUseProdDmd Int
n UseDmd
UHead = [ArgUse] -> Maybe [ArgUse]
forall a. a -> Maybe a
Just (Int -> ArgUse -> [ArgUse]
forall a. Int -> a -> [a]
replicate Int
n ArgUse
forall u. Use u
Abs)
splitUseProdDmd Int
n (UProd [ArgUse]
ds) = WARN( not (ds `lengthIs` n),
text "splitUseProdDmd" $$ ppr n
$$ ppr ds )
[ArgUse] -> Maybe [ArgUse]
forall a. a -> Maybe a
Just [ArgUse]
ds
splitUseProdDmd Int
_ (UCall Count
_ UseDmd
_) = Maybe [ArgUse]
forall a. Maybe a
Nothing
useCount :: Use u -> Count
useCount :: Use u -> Count
useCount Use u
Abs = Count
One
useCount (Use Count
One u
_) = Count
One
useCount Use u
_ = Count
Many
type CleanDemand = JointDmd StrDmd UseDmd
bothCleanDmd :: CleanDemand -> CleanDemand -> CleanDemand
bothCleanDmd :: CleanDemand -> CleanDemand -> CleanDemand
bothCleanDmd (JD { sd :: forall s u. JointDmd s u -> s
sd = StrDmd
s1, ud :: forall s u. JointDmd s u -> u
ud = UseDmd
a1}) (JD { sd :: forall s u. JointDmd s u -> s
sd = StrDmd
s2, ud :: forall s u. JointDmd s u -> u
ud = UseDmd
a2})
= JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: StrDmd
sd = StrDmd
s1 StrDmd -> StrDmd -> StrDmd
`bothStr` StrDmd
s2, ud :: UseDmd
ud = UseDmd
a1 UseDmd -> UseDmd -> UseDmd
`bothUse` UseDmd
a2 }
mkHeadStrict :: CleanDemand -> CleanDemand
mkHeadStrict :: CleanDemand -> CleanDemand
mkHeadStrict CleanDemand
cd = CleanDemand
cd { sd :: StrDmd
sd = StrDmd
HeadStr }
mkOnceUsedDmd, mkManyUsedDmd :: CleanDemand -> Demand
mkOnceUsedDmd :: CleanDemand -> Demand
mkOnceUsedDmd (JD {sd :: forall s u. JointDmd s u -> s
sd = StrDmd
s,ud :: forall s u. JointDmd s u -> u
ud = UseDmd
a}) = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str ExnStr
VanStr StrDmd
s, ud :: ArgUse
ud = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
One UseDmd
a }
mkManyUsedDmd :: CleanDemand -> Demand
mkManyUsedDmd (JD {sd :: forall s u. JointDmd s u -> s
sd = StrDmd
s,ud :: forall s u. JointDmd s u -> u
ud = UseDmd
a}) = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str ExnStr
VanStr StrDmd
s, ud :: ArgUse
ud = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
Many UseDmd
a }
evalDmd :: Demand
evalDmd :: Demand
evalDmd = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str ExnStr
VanStr StrDmd
HeadStr, ud :: ArgUse
ud = ArgUse
useTop }
mkProdDmd :: [Demand] -> CleanDemand
mkProdDmd :: [Demand] -> CleanDemand
mkProdDmd [Demand]
dx
= JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: StrDmd
sd = [ArgStr] -> StrDmd
mkSProd ([ArgStr] -> StrDmd) -> [ArgStr] -> StrDmd
forall a b. (a -> b) -> a -> b
$ (Demand -> ArgStr) -> [Demand] -> [ArgStr]
forall a b. (a -> b) -> [a] -> [b]
map Demand -> ArgStr
forall s u. JointDmd s u -> s
getStrDmd [Demand]
dx
, ud :: UseDmd
ud = [ArgUse] -> UseDmd
mkUProd ([ArgUse] -> UseDmd) -> [ArgUse] -> UseDmd
forall a b. (a -> b) -> a -> b
$ (Demand -> ArgUse) -> [Demand] -> [ArgUse]
forall a b. (a -> b) -> [a] -> [b]
map Demand -> ArgUse
forall s u. JointDmd s u -> u
getUseDmd [Demand]
dx }
mkCallDmd :: CleanDemand -> CleanDemand
mkCallDmd :: CleanDemand -> CleanDemand
mkCallDmd (JD {sd :: forall s u. JointDmd s u -> s
sd = StrDmd
d, ud :: forall s u. JointDmd s u -> u
ud = UseDmd
u})
= JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: StrDmd
sd = StrDmd -> StrDmd
mkSCall StrDmd
d, ud :: UseDmd
ud = Count -> UseDmd -> UseDmd
mkUCall Count
One UseDmd
u }
mkWorkerDemand :: Int -> Demand
mkWorkerDemand :: Int -> Demand
mkWorkerDemand Int
n = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ArgStr
forall s. Str s
Lazy, ud :: ArgUse
ud = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
One (Int -> UseDmd
forall t. (Eq t, Num t) => t -> UseDmd
go Int
n) }
where go :: t -> UseDmd
go t
0 = UseDmd
Used
go t
n = Count -> UseDmd -> UseDmd
mkUCall Count
One (UseDmd -> UseDmd) -> UseDmd -> UseDmd
forall a b. (a -> b) -> a -> b
$ t -> UseDmd
go (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1)
cleanEvalDmd :: CleanDemand
cleanEvalDmd :: CleanDemand
cleanEvalDmd = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: StrDmd
sd = StrDmd
HeadStr, ud :: UseDmd
ud = UseDmd
Used }
cleanEvalProdDmd :: Arity -> CleanDemand
cleanEvalProdDmd :: Int -> CleanDemand
cleanEvalProdDmd Int
n = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: StrDmd
sd = StrDmd
HeadStr, ud :: UseDmd
ud = [ArgUse] -> UseDmd
UProd (Int -> ArgUse -> [ArgUse]
forall a. Int -> a -> [a]
replicate Int
n ArgUse
useTop) }
type Demand = JointDmd ArgStr ArgUse
lubDmd :: Demand -> Demand -> Demand
lubDmd :: Demand -> Demand -> Demand
lubDmd (JD {sd :: forall s u. JointDmd s u -> s
sd = ArgStr
s1, ud :: forall s u. JointDmd s u -> u
ud = ArgUse
a1}) (JD {sd :: forall s u. JointDmd s u -> s
sd = ArgStr
s2, ud :: forall s u. JointDmd s u -> u
ud = ArgUse
a2})
= JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ArgStr
s1 ArgStr -> ArgStr -> ArgStr
`lubArgStr` ArgStr
s2
, ud :: ArgUse
ud = ArgUse
a1 ArgUse -> ArgUse -> ArgUse
`lubArgUse` ArgUse
a2 }
bothDmd :: Demand -> Demand -> Demand
bothDmd :: Demand -> Demand -> Demand
bothDmd (JD {sd :: forall s u. JointDmd s u -> s
sd = ArgStr
s1, ud :: forall s u. JointDmd s u -> u
ud = ArgUse
a1}) (JD {sd :: forall s u. JointDmd s u -> s
sd = ArgStr
s2, ud :: forall s u. JointDmd s u -> u
ud = ArgUse
a2})
= JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ArgStr
s1 ArgStr -> ArgStr -> ArgStr
`bothArgStr` ArgStr
s2
, ud :: ArgUse
ud = ArgUse
a1 ArgUse -> ArgUse -> ArgUse
`bothArgUse` ArgUse
a2 }
lazyApply1Dmd, lazyApply2Dmd, strictApply1Dmd, catchArgDmd :: Demand
strictApply1Dmd :: Demand
strictApply1Dmd = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str ExnStr
VanStr (StrDmd -> StrDmd
SCall StrDmd
HeadStr)
, ud :: ArgUse
ud = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
Many (Count -> UseDmd -> UseDmd
UCall Count
One UseDmd
Used) }
catchArgDmd :: Demand
catchArgDmd = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str ExnStr
ExnStr (StrDmd -> StrDmd
SCall StrDmd
HeadStr)
, ud :: ArgUse
ud = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
One (Count -> UseDmd -> UseDmd
UCall Count
One UseDmd
Used) }
lazyApply1Dmd :: Demand
lazyApply1Dmd = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ArgStr
forall s. Str s
Lazy
, ud :: ArgUse
ud = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
One (Count -> UseDmd -> UseDmd
UCall Count
One UseDmd
Used) }
lazyApply2Dmd :: Demand
lazyApply2Dmd = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ArgStr
forall s. Str s
Lazy
, ud :: ArgUse
ud = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
One (Count -> UseDmd -> UseDmd
UCall Count
One (Count -> UseDmd -> UseDmd
UCall Count
One UseDmd
Used)) }
absDmd :: Demand
absDmd :: Demand
absDmd = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ArgStr
forall s. Str s
Lazy, ud :: ArgUse
ud = ArgUse
forall u. Use u
Abs }
topDmd :: Demand
topDmd :: Demand
topDmd = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ArgStr
forall s. Str s
Lazy, ud :: ArgUse
ud = ArgUse
useTop }
botDmd :: Demand
botDmd :: Demand
botDmd = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ArgStr
strBot, ud :: ArgUse
ud = ArgUse
useBot }
seqDmd :: Demand
seqDmd :: Demand
seqDmd = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str ExnStr
VanStr StrDmd
HeadStr, ud :: ArgUse
ud = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
One UseDmd
UHead }
oneifyDmd :: JointDmd s (Use u) -> JointDmd s (Use u)
oneifyDmd :: JointDmd s (Use u) -> JointDmd s (Use u)
oneifyDmd (JD { sd :: forall s u. JointDmd s u -> s
sd = s
s, ud :: forall s u. JointDmd s u -> u
ud = Use Count
_ u
a }) = JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: s
sd = s
s, ud :: Use u
ud = Count -> u -> Use u
forall u. Count -> u -> Use u
Use Count
One u
a }
oneifyDmd JointDmd s (Use u)
jd = JointDmd s (Use u)
jd
isTopDmd :: Demand -> Bool
isTopDmd :: Demand -> Bool
isTopDmd (JD {sd :: forall s u. JointDmd s u -> s
sd = ArgStr
Lazy, ud :: forall s u. JointDmd s u -> u
ud = Use Count
Many UseDmd
Used}) = Bool
True
isTopDmd Demand
_ = Bool
False
isAbsDmd :: JointDmd (Str s) (Use u) -> Bool
isAbsDmd :: JointDmd (Str s) (Use u) -> Bool
isAbsDmd (JD {ud :: forall s u. JointDmd s u -> u
ud = Use u
Abs}) = Bool
True
isAbsDmd JointDmd (Str s) (Use u)
_ = Bool
False
isSeqDmd :: Demand -> Bool
isSeqDmd :: Demand -> Bool
isSeqDmd (JD {sd :: forall s u. JointDmd s u -> s
sd = Str ExnStr
VanStr StrDmd
HeadStr, ud :: forall s u. JointDmd s u -> u
ud = Use Count
_ UseDmd
UHead}) = Bool
True
isSeqDmd Demand
_ = Bool
False
isUsedOnce :: JointDmd (Str s) (Use u) -> Bool
isUsedOnce :: JointDmd (Str s) (Use u) -> Bool
isUsedOnce (JD { ud :: forall s u. JointDmd s u -> u
ud = Use u
a }) = case Use u -> Count
forall u. Use u -> Count
useCount Use u
a of
Count
One -> Bool
True
Count
Many -> Bool
False
seqDemand :: Demand -> ()
seqDemand :: Demand -> ()
seqDemand (JD {sd :: forall s u. JointDmd s u -> s
sd = ArgStr
s, ud :: forall s u. JointDmd s u -> u
ud = ArgUse
u}) = ArgStr -> ()
seqArgStr ArgStr
s () -> () -> ()
`seq` ArgUse -> ()
seqArgUse ArgUse
u
seqDemandList :: [Demand] -> ()
seqDemandList :: [Demand] -> ()
seqDemandList [] = ()
seqDemandList (Demand
d:[Demand]
ds) = Demand -> ()
seqDemand Demand
d () -> () -> ()
`seq` [Demand] -> ()
seqDemandList [Demand]
ds
isStrictDmd :: JointDmd (Str s) (Use u) -> Bool
isStrictDmd :: JointDmd (Str s) (Use u) -> Bool
isStrictDmd (JD {ud :: forall s u. JointDmd s u -> u
ud = Use u
Abs}) = Bool
False
isStrictDmd (JD {sd :: forall s u. JointDmd s u -> s
sd = Str s
Lazy}) = Bool
False
isStrictDmd JointDmd (Str s) (Use u)
_ = Bool
True
isWeakDmd :: Demand -> Bool
isWeakDmd :: Demand -> Bool
isWeakDmd (JD {sd :: forall s u. JointDmd s u -> s
sd = ArgStr
s, ud :: forall s u. JointDmd s u -> u
ud = ArgUse
a}) = ArgStr -> Bool
isLazy ArgStr
s Bool -> Bool -> Bool
&& ArgUse -> Bool
isUsedMU ArgUse
a
cleanUseDmd_maybe :: Demand -> Maybe UseDmd
cleanUseDmd_maybe :: Demand -> Maybe UseDmd
cleanUseDmd_maybe (JD { ud :: forall s u. JointDmd s u -> u
ud = Use Count
_ UseDmd
u }) = UseDmd -> Maybe UseDmd
forall a. a -> Maybe a
Just UseDmd
u
cleanUseDmd_maybe Demand
_ = Maybe UseDmd
forall a. Maybe a
Nothing
splitFVs :: Bool
-> DmdEnv -> (DmdEnv, DmdEnv)
splitFVs :: Bool -> DmdEnv -> (DmdEnv, DmdEnv)
splitFVs Bool
is_thunk DmdEnv
rhs_fvs
| Bool
is_thunk = (Unique -> Demand -> (DmdEnv, DmdEnv) -> (DmdEnv, DmdEnv))
-> (DmdEnv, DmdEnv) -> DmdEnv -> (DmdEnv, DmdEnv)
forall elt a. (Unique -> elt -> a -> a) -> a -> UniqFM elt -> a
nonDetFoldUFM_Directly Unique -> Demand -> (DmdEnv, DmdEnv) -> (DmdEnv, DmdEnv)
forall s u u.
Unique
-> JointDmd (Str s) u
-> (UniqFM (JointDmd (Str s) u), UniqFM (JointDmd (Str s) (Use u)))
-> (UniqFM (JointDmd (Str s) u), UniqFM (JointDmd (Str s) (Use u)))
add (DmdEnv
forall a. VarEnv a
emptyVarEnv, DmdEnv
forall a. VarEnv a
emptyVarEnv) DmdEnv
rhs_fvs
| Bool
otherwise = (Demand -> Bool) -> DmdEnv -> (DmdEnv, DmdEnv)
forall a. (a -> Bool) -> VarEnv a -> (VarEnv a, VarEnv a)
partitionVarEnv Demand -> Bool
isWeakDmd DmdEnv
rhs_fvs
where
add :: Unique
-> JointDmd (Str s) u
-> (UniqFM (JointDmd (Str s) u), UniqFM (JointDmd (Str s) (Use u)))
-> (UniqFM (JointDmd (Str s) u), UniqFM (JointDmd (Str s) (Use u)))
add Unique
uniq dmd :: JointDmd (Str s) u
dmd@(JD { sd :: forall s u. JointDmd s u -> s
sd = Str s
s, ud :: forall s u. JointDmd s u -> u
ud = u
u }) (UniqFM (JointDmd (Str s) u)
lazy_fv, UniqFM (JointDmd (Str s) (Use u))
sig_fv)
| Str s
Lazy <- Str s
s = (UniqFM (JointDmd (Str s) u)
-> Unique -> JointDmd (Str s) u -> UniqFM (JointDmd (Str s) u)
forall elt. UniqFM elt -> Unique -> elt -> UniqFM elt
addToUFM_Directly UniqFM (JointDmd (Str s) u)
lazy_fv Unique
uniq JointDmd (Str s) u
dmd, UniqFM (JointDmd (Str s) (Use u))
sig_fv)
| Bool
otherwise = ( UniqFM (JointDmd (Str s) u)
-> Unique -> JointDmd (Str s) u -> UniqFM (JointDmd (Str s) u)
forall elt. UniqFM elt -> Unique -> elt -> UniqFM elt
addToUFM_Directly UniqFM (JointDmd (Str s) u)
lazy_fv Unique
uniq (JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: Str s
sd = Str s
forall s. Str s
Lazy, ud :: u
ud = u
u })
, UniqFM (JointDmd (Str s) (Use u))
-> Unique
-> JointDmd (Str s) (Use u)
-> UniqFM (JointDmd (Str s) (Use u))
forall elt. UniqFM elt -> Unique -> elt -> UniqFM elt
addToUFM_Directly UniqFM (JointDmd (Str s) (Use u))
sig_fv Unique
uniq (JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: Str s
sd = Str s
s, ud :: Use u
ud = Use u
forall u. Use u
Abs }) )
data TypeShape = TsFun TypeShape
| TsProd [TypeShape]
| TsUnk
instance Outputable TypeShape where
ppr :: TypeShape -> SDoc
ppr TypeShape
TsUnk = String -> SDoc
text String
"TsUnk"
ppr (TsFun TypeShape
ts) = String -> SDoc
text String
"TsFun" SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
parens (TypeShape -> SDoc
forall a. Outputable a => a -> SDoc
ppr TypeShape
ts)
ppr (TsProd [TypeShape]
tss) = SDoc -> SDoc
parens ([SDoc] -> SDoc
hsep ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma ([SDoc] -> [SDoc]) -> [SDoc] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ (TypeShape -> SDoc) -> [TypeShape] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map TypeShape -> SDoc
forall a. Outputable a => a -> SDoc
ppr [TypeShape]
tss)
trimToType :: Demand -> TypeShape -> Demand
trimToType :: Demand -> TypeShape -> Demand
trimToType (JD { sd :: forall s u. JointDmd s u -> s
sd = ArgStr
ms, ud :: forall s u. JointDmd s u -> u
ud = ArgUse
mu }) TypeShape
ts
= ArgStr -> ArgUse -> Demand
forall s u. s -> u -> JointDmd s u
JD (ArgStr -> TypeShape -> ArgStr
go_ms ArgStr
ms TypeShape
ts) (ArgUse -> TypeShape -> ArgUse
go_mu ArgUse
mu TypeShape
ts)
where
go_ms :: ArgStr -> TypeShape -> ArgStr
go_ms :: ArgStr -> TypeShape -> ArgStr
go_ms ArgStr
Lazy TypeShape
_ = ArgStr
forall s. Str s
Lazy
go_ms (Str ExnStr
x StrDmd
s) TypeShape
ts = ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str ExnStr
x (StrDmd -> TypeShape -> StrDmd
go_s StrDmd
s TypeShape
ts)
go_s :: StrDmd -> TypeShape -> StrDmd
go_s :: StrDmd -> TypeShape -> StrDmd
go_s StrDmd
HyperStr TypeShape
_ = StrDmd
HyperStr
go_s (SCall StrDmd
s) (TsFun TypeShape
ts) = StrDmd -> StrDmd
SCall (StrDmd -> TypeShape -> StrDmd
go_s StrDmd
s TypeShape
ts)
go_s (SProd [ArgStr]
mss) (TsProd [TypeShape]
tss)
| [ArgStr] -> [TypeShape] -> Bool
forall a b. [a] -> [b] -> Bool
equalLength [ArgStr]
mss [TypeShape]
tss = [ArgStr] -> StrDmd
SProd ((ArgStr -> TypeShape -> ArgStr)
-> [ArgStr] -> [TypeShape] -> [ArgStr]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ArgStr -> TypeShape -> ArgStr
go_ms [ArgStr]
mss [TypeShape]
tss)
go_s StrDmd
_ TypeShape
_ = StrDmd
HeadStr
go_mu :: ArgUse -> TypeShape -> ArgUse
go_mu :: ArgUse -> TypeShape -> ArgUse
go_mu ArgUse
Abs TypeShape
_ = ArgUse
forall u. Use u
Abs
go_mu (Use Count
c UseDmd
u) TypeShape
ts = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
c (UseDmd -> TypeShape -> UseDmd
go_u UseDmd
u TypeShape
ts)
go_u :: UseDmd -> TypeShape -> UseDmd
go_u :: UseDmd -> TypeShape -> UseDmd
go_u UseDmd
UHead TypeShape
_ = UseDmd
UHead
go_u (UCall Count
c UseDmd
u) (TsFun TypeShape
ts) = Count -> UseDmd -> UseDmd
UCall Count
c (UseDmd -> TypeShape -> UseDmd
go_u UseDmd
u TypeShape
ts)
go_u (UProd [ArgUse]
mus) (TsProd [TypeShape]
tss)
| [ArgUse] -> [TypeShape] -> Bool
forall a b. [a] -> [b] -> Bool
equalLength [ArgUse]
mus [TypeShape]
tss = [ArgUse] -> UseDmd
UProd ((ArgUse -> TypeShape -> ArgUse)
-> [ArgUse] -> [TypeShape] -> [ArgUse]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ArgUse -> TypeShape -> ArgUse
go_mu [ArgUse]
mus [TypeShape]
tss)
go_u UseDmd
_ TypeShape
_ = UseDmd
Used
splitProdDmd_maybe :: Demand -> Maybe [Demand]
splitProdDmd_maybe :: Demand -> Maybe [Demand]
splitProdDmd_maybe (JD { sd :: forall s u. JointDmd s u -> s
sd = ArgStr
s, ud :: forall s u. JointDmd s u -> u
ud = ArgUse
u })
= case (ArgStr
s,ArgUse
u) of
(Str ExnStr
_ (SProd [ArgStr]
sx), Use Count
_ UseDmd
u) | Just [ArgUse]
ux <- Int -> UseDmd -> Maybe [ArgUse]
splitUseProdDmd ([ArgStr] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ArgStr]
sx) UseDmd
u
-> [Demand] -> Maybe [Demand]
forall a. a -> Maybe a
Just ([ArgStr] -> [ArgUse] -> [Demand]
forall s u. [s] -> [u] -> [JointDmd s u]
mkJointDmds [ArgStr]
sx [ArgUse]
ux)
(Str ExnStr
_ StrDmd
s, Use Count
_ (UProd [ArgUse]
ux)) | Just [ArgStr]
sx <- Int -> StrDmd -> Maybe [ArgStr]
splitStrProdDmd ([ArgUse] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ArgUse]
ux) StrDmd
s
-> [Demand] -> Maybe [Demand]
forall a. a -> Maybe a
Just ([ArgStr] -> [ArgUse] -> [Demand]
forall s u. [s] -> [u] -> [JointDmd s u]
mkJointDmds [ArgStr]
sx [ArgUse]
ux)
(ArgStr
Lazy, Use Count
_ (UProd [ArgUse]
ux)) -> [Demand] -> Maybe [Demand]
forall a. a -> Maybe a
Just ([ArgStr] -> [ArgUse] -> [Demand]
forall s u. [s] -> [u] -> [JointDmd s u]
mkJointDmds (Int -> ArgStr -> [ArgStr]
forall a. Int -> a -> [a]
replicate ([ArgUse] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ArgUse]
ux) ArgStr
forall s. Str s
Lazy) [ArgUse]
ux)
(ArgStr, ArgUse)
_ -> Maybe [Demand]
forall a. Maybe a
Nothing
data Termination r
= Diverges
| ThrowsExn
| Dunno r
deriving( Termination r -> Termination r -> Bool
(Termination r -> Termination r -> Bool)
-> (Termination r -> Termination r -> Bool) -> Eq (Termination r)
forall r. Eq r => Termination r -> Termination r -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Termination r -> Termination r -> Bool
$c/= :: forall r. Eq r => Termination r -> Termination r -> Bool
== :: Termination r -> Termination r -> Bool
$c== :: forall r. Eq r => Termination r -> Termination r -> Bool
Eq, Int -> Termination r -> ShowS
[Termination r] -> ShowS
Termination r -> String
(Int -> Termination r -> ShowS)
-> (Termination r -> String)
-> ([Termination r] -> ShowS)
-> Show (Termination r)
forall r. Show r => Int -> Termination r -> ShowS
forall r. Show r => [Termination r] -> ShowS
forall r. Show r => Termination r -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Termination r] -> ShowS
$cshowList :: forall r. Show r => [Termination r] -> ShowS
show :: Termination r -> String
$cshow :: forall r. Show r => Termination r -> String
showsPrec :: Int -> Termination r -> ShowS
$cshowsPrec :: forall r. Show r => Int -> Termination r -> ShowS
Show )
type DmdResult = Termination CPRResult
data CPRResult = NoCPR
| RetProd
| RetSum ConTag
deriving( CPRResult -> CPRResult -> Bool
(CPRResult -> CPRResult -> Bool)
-> (CPRResult -> CPRResult -> Bool) -> Eq CPRResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CPRResult -> CPRResult -> Bool
$c/= :: CPRResult -> CPRResult -> Bool
== :: CPRResult -> CPRResult -> Bool
$c== :: CPRResult -> CPRResult -> Bool
Eq, Int -> CPRResult -> ShowS
[CPRResult] -> ShowS
CPRResult -> String
(Int -> CPRResult -> ShowS)
-> (CPRResult -> String)
-> ([CPRResult] -> ShowS)
-> Show CPRResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CPRResult] -> ShowS
$cshowList :: [CPRResult] -> ShowS
show :: CPRResult -> String
$cshow :: CPRResult -> String
showsPrec :: Int -> CPRResult -> ShowS
$cshowsPrec :: Int -> CPRResult -> ShowS
Show )
lubCPR :: CPRResult -> CPRResult -> CPRResult
lubCPR :: CPRResult -> CPRResult -> CPRResult
lubCPR (RetSum Int
t1) (RetSum Int
t2)
| Int
t1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
t2 = Int -> CPRResult
RetSum Int
t1
lubCPR CPRResult
RetProd CPRResult
RetProd = CPRResult
RetProd
lubCPR CPRResult
_ CPRResult
_ = CPRResult
NoCPR
lubDmdResult :: DmdResult -> DmdResult -> DmdResult
lubDmdResult :: DmdResult -> DmdResult -> DmdResult
lubDmdResult DmdResult
Diverges DmdResult
r = DmdResult
r
lubDmdResult DmdResult
ThrowsExn DmdResult
Diverges = DmdResult
forall r. Termination r
ThrowsExn
lubDmdResult DmdResult
ThrowsExn DmdResult
r = DmdResult
r
lubDmdResult (Dunno CPRResult
c1) DmdResult
Diverges = CPRResult -> DmdResult
forall r. r -> Termination r
Dunno CPRResult
c1
lubDmdResult (Dunno CPRResult
c1) DmdResult
ThrowsExn = CPRResult -> DmdResult
forall r. r -> Termination r
Dunno CPRResult
c1
lubDmdResult (Dunno CPRResult
c1) (Dunno CPRResult
c2) = CPRResult -> DmdResult
forall r. r -> Termination r
Dunno (CPRResult
c1 CPRResult -> CPRResult -> CPRResult
`lubCPR` CPRResult
c2)
bothDmdResult :: DmdResult -> Termination () -> DmdResult
bothDmdResult :: DmdResult -> Termination () -> DmdResult
bothDmdResult DmdResult
_ Termination ()
Diverges = DmdResult
forall r. Termination r
Diverges
bothDmdResult DmdResult
r Termination ()
ThrowsExn = case DmdResult
r of { DmdResult
Diverges -> DmdResult
r; DmdResult
_ -> DmdResult
forall r. Termination r
ThrowsExn }
bothDmdResult DmdResult
r (Dunno {}) = DmdResult
r
instance Outputable r => Outputable (Termination r) where
ppr :: Termination r -> SDoc
ppr Termination r
Diverges = Char -> SDoc
char Char
'b'
ppr Termination r
ThrowsExn = Char -> SDoc
char Char
'x'
ppr (Dunno r
c) = r -> SDoc
forall a. Outputable a => a -> SDoc
ppr r
c
instance Outputable CPRResult where
ppr :: CPRResult -> SDoc
ppr CPRResult
NoCPR = SDoc
empty
ppr (RetSum Int
n) = Char -> SDoc
char Char
'm' SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
n
ppr CPRResult
RetProd = Char -> SDoc
char Char
'm'
seqDmdResult :: DmdResult -> ()
seqDmdResult :: DmdResult -> ()
seqDmdResult DmdResult
Diverges = ()
seqDmdResult DmdResult
ThrowsExn = ()
seqDmdResult (Dunno CPRResult
c) = CPRResult -> ()
seqCPRResult CPRResult
c
seqCPRResult :: CPRResult -> ()
seqCPRResult :: CPRResult -> ()
seqCPRResult CPRResult
NoCPR = ()
seqCPRResult (RetSum Int
n) = Int
n Int -> () -> ()
`seq` ()
seqCPRResult CPRResult
RetProd = ()
topRes, exnRes, botRes :: DmdResult
topRes :: DmdResult
topRes = CPRResult -> DmdResult
forall r. r -> Termination r
Dunno CPRResult
NoCPR
exnRes :: DmdResult
exnRes = DmdResult
forall r. Termination r
ThrowsExn
botRes :: DmdResult
botRes = DmdResult
forall r. Termination r
Diverges
cprSumRes :: ConTag -> DmdResult
cprSumRes :: Int -> DmdResult
cprSumRes Int
tag = CPRResult -> DmdResult
forall r. r -> Termination r
Dunno (CPRResult -> DmdResult) -> CPRResult -> DmdResult
forall a b. (a -> b) -> a -> b
$ Int -> CPRResult
RetSum Int
tag
cprProdRes :: [DmdType] -> DmdResult
cprProdRes :: [DmdType] -> DmdResult
cprProdRes [DmdType]
_arg_tys = CPRResult -> DmdResult
forall r. r -> Termination r
Dunno (CPRResult -> DmdResult) -> CPRResult -> DmdResult
forall a b. (a -> b) -> a -> b
$ CPRResult
RetProd
vanillaCprProdRes :: Arity -> DmdResult
vanillaCprProdRes :: Int -> DmdResult
vanillaCprProdRes Int
_arity = CPRResult -> DmdResult
forall r. r -> Termination r
Dunno (CPRResult -> DmdResult) -> CPRResult -> DmdResult
forall a b. (a -> b) -> a -> b
$ CPRResult
RetProd
isTopRes :: DmdResult -> Bool
isTopRes :: DmdResult -> Bool
isTopRes (Dunno CPRResult
NoCPR) = Bool
True
isTopRes DmdResult
_ = Bool
False
isBotRes :: DmdResult -> Bool
isBotRes :: DmdResult -> Bool
isBotRes DmdResult
Diverges = Bool
True
isBotRes DmdResult
ThrowsExn = Bool
True
isBotRes (Dunno {}) = Bool
False
trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult
trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult
trimCPRInfo Bool
trim_all Bool
trim_sums DmdResult
res
= DmdResult -> DmdResult
trimR DmdResult
res
where
trimR :: DmdResult -> DmdResult
trimR (Dunno CPRResult
c) = CPRResult -> DmdResult
forall r. r -> Termination r
Dunno (CPRResult -> CPRResult
trimC CPRResult
c)
trimR DmdResult
res = DmdResult
res
trimC :: CPRResult -> CPRResult
trimC (RetSum Int
n) | Bool
trim_all Bool -> Bool -> Bool
|| Bool
trim_sums = CPRResult
NoCPR
| Bool
otherwise = Int -> CPRResult
RetSum Int
n
trimC CPRResult
RetProd | Bool
trim_all = CPRResult
NoCPR
| Bool
otherwise = CPRResult
RetProd
trimC CPRResult
NoCPR = CPRResult
NoCPR
returnsCPR_maybe :: DmdResult -> Maybe ConTag
returnsCPR_maybe :: DmdResult -> Maybe Int
returnsCPR_maybe (Dunno CPRResult
c) = CPRResult -> Maybe Int
retCPR_maybe CPRResult
c
returnsCPR_maybe DmdResult
_ = Maybe Int
forall a. Maybe a
Nothing
retCPR_maybe :: CPRResult -> Maybe ConTag
retCPR_maybe :: CPRResult -> Maybe Int
retCPR_maybe (RetSum Int
t) = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
t
retCPR_maybe CPRResult
RetProd = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
fIRST_TAG
retCPR_maybe CPRResult
NoCPR = Maybe Int
forall a. Maybe a
Nothing
defaultDmd :: Termination r -> Demand
defaultDmd :: Termination r -> Demand
defaultDmd (Dunno {}) = Demand
absDmd
defaultDmd Termination r
_ = Demand
botDmd
resTypeArgDmd :: Termination r -> Demand
resTypeArgDmd :: Termination r -> Demand
resTypeArgDmd (Dunno r
_) = Demand
topDmd
resTypeArgDmd Termination r
_ = Demand
botDmd
type DmdEnv = VarEnv Demand
data DmdType = DmdType
DmdEnv
[Demand]
DmdResult
instance Eq DmdType where
== :: DmdType -> DmdType -> Bool
(==) (DmdType DmdEnv
fv1 [Demand]
ds1 DmdResult
res1)
(DmdType DmdEnv
fv2 [Demand]
ds2 DmdResult
res2) = DmdEnv -> [(Unique, Demand)]
forall elt. UniqFM elt -> [(Unique, elt)]
nonDetUFMToList DmdEnv
fv1 [(Unique, Demand)] -> [(Unique, Demand)] -> Bool
forall a. Eq a => a -> a -> Bool
== DmdEnv -> [(Unique, Demand)]
forall elt. UniqFM elt -> [(Unique, elt)]
nonDetUFMToList DmdEnv
fv2
Bool -> Bool -> Bool
&& [Demand]
ds1 [Demand] -> [Demand] -> Bool
forall a. Eq a => a -> a -> Bool
== [Demand]
ds2 Bool -> Bool -> Bool
&& DmdResult
res1 DmdResult -> DmdResult -> Bool
forall a. Eq a => a -> a -> Bool
== DmdResult
res2
lubDmdType :: DmdType -> DmdType -> DmdType
lubDmdType :: DmdType -> DmdType -> DmdType
lubDmdType DmdType
d1 DmdType
d2
= DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
lub_fv [Demand]
lub_ds DmdResult
lub_res
where
n :: Int
n = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max (DmdType -> Int
dmdTypeDepth DmdType
d1) (DmdType -> Int
dmdTypeDepth DmdType
d2)
(DmdType DmdEnv
fv1 [Demand]
ds1 DmdResult
r1) = Int -> DmdType -> DmdType
ensureArgs Int
n DmdType
d1
(DmdType DmdEnv
fv2 [Demand]
ds2 DmdResult
r2) = Int -> DmdType -> DmdType
ensureArgs Int
n DmdType
d2
lub_fv :: DmdEnv
lub_fv = (Demand -> Demand -> Demand)
-> DmdEnv -> Demand -> DmdEnv -> Demand -> DmdEnv
forall a.
(a -> a -> a) -> VarEnv a -> a -> VarEnv a -> a -> VarEnv a
plusVarEnv_CD Demand -> Demand -> Demand
lubDmd DmdEnv
fv1 (DmdResult -> Demand
forall r. Termination r -> Demand
defaultDmd DmdResult
r1) DmdEnv
fv2 (DmdResult -> Demand
forall r. Termination r -> Demand
defaultDmd DmdResult
r2)
lub_ds :: [Demand]
lub_ds = String
-> (Demand -> Demand -> Demand) -> [Demand] -> [Demand] -> [Demand]
forall a b c. String -> (a -> b -> c) -> [a] -> [b] -> [c]
zipWithEqual String
"lubDmdType" Demand -> Demand -> Demand
lubDmd [Demand]
ds1 [Demand]
ds2
lub_res :: DmdResult
lub_res = DmdResult -> DmdResult -> DmdResult
lubDmdResult DmdResult
r1 DmdResult
r2
type BothDmdArg = (DmdEnv, Termination ())
mkBothDmdArg :: DmdEnv -> BothDmdArg
mkBothDmdArg :: DmdEnv -> BothDmdArg
mkBothDmdArg DmdEnv
env = (DmdEnv
env, () -> Termination ()
forall r. r -> Termination r
Dunno ())
toBothDmdArg :: DmdType -> BothDmdArg
toBothDmdArg :: DmdType -> BothDmdArg
toBothDmdArg (DmdType DmdEnv
fv [Demand]
_ DmdResult
r) = (DmdEnv
fv, DmdResult -> Termination ()
forall r. Termination r -> Termination ()
go DmdResult
r)
where
go :: Termination r -> Termination ()
go (Dunno {}) = () -> Termination ()
forall r. r -> Termination r
Dunno ()
go Termination r
ThrowsExn = Termination ()
forall r. Termination r
ThrowsExn
go Termination r
Diverges = Termination ()
forall r. Termination r
Diverges
bothDmdType :: DmdType -> BothDmdArg -> DmdType
bothDmdType :: DmdType -> BothDmdArg -> DmdType
bothDmdType (DmdType DmdEnv
fv1 [Demand]
ds1 DmdResult
r1) (DmdEnv
fv2, Termination ()
t2)
= DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType ((Demand -> Demand -> Demand)
-> DmdEnv -> Demand -> DmdEnv -> Demand -> DmdEnv
forall a.
(a -> a -> a) -> VarEnv a -> a -> VarEnv a -> a -> VarEnv a
plusVarEnv_CD Demand -> Demand -> Demand
bothDmd DmdEnv
fv1 (DmdResult -> Demand
forall r. Termination r -> Demand
defaultDmd DmdResult
r1) DmdEnv
fv2 (Termination () -> Demand
forall r. Termination r -> Demand
defaultDmd Termination ()
t2))
[Demand]
ds1
(DmdResult
r1 DmdResult -> Termination () -> DmdResult
`bothDmdResult` Termination ()
t2)
instance Outputable DmdType where
ppr :: DmdType -> SDoc
ppr (DmdType DmdEnv
fv [Demand]
ds DmdResult
res)
= [SDoc] -> SDoc
hsep [[SDoc] -> SDoc
hcat ((Demand -> SDoc) -> [Demand] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Demand -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Demand]
ds) SDoc -> SDoc -> SDoc
<> DmdResult -> SDoc
forall a. Outputable a => a -> SDoc
ppr DmdResult
res,
if [(Unique, Demand)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Unique, Demand)]
fv_elts then SDoc
empty
else SDoc -> SDoc
braces ([SDoc] -> SDoc
fsep (((Unique, Demand) -> SDoc) -> [(Unique, Demand)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (Unique, Demand) -> SDoc
forall a a. (Outputable a, Outputable a) => (a, a) -> SDoc
pp_elt [(Unique, Demand)]
fv_elts))]
where
pp_elt :: (a, a) -> SDoc
pp_elt (a
uniq, a
dmd) = a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
uniq SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"->" SDoc -> SDoc -> SDoc
<> a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
dmd
fv_elts :: [(Unique, Demand)]
fv_elts = DmdEnv -> [(Unique, Demand)]
forall elt. UniqFM elt -> [(Unique, elt)]
nonDetUFMToList DmdEnv
fv
emptyDmdEnv :: VarEnv Demand
emptyDmdEnv :: DmdEnv
emptyDmdEnv = DmdEnv
forall a. VarEnv a
emptyVarEnv
nopDmdType, botDmdType, exnDmdType :: DmdType
nopDmdType :: DmdType
nopDmdType = DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
emptyDmdEnv [] DmdResult
topRes
botDmdType :: DmdType
botDmdType = DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
emptyDmdEnv [] DmdResult
botRes
exnDmdType :: DmdType
exnDmdType = DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
emptyDmdEnv [] DmdResult
exnRes
cprProdDmdType :: Arity -> DmdType
cprProdDmdType :: Int -> DmdType
cprProdDmdType Int
arity
= DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
emptyDmdEnv [] (Int -> DmdResult
vanillaCprProdRes Int
arity)
isTopDmdType :: DmdType -> Bool
isTopDmdType :: DmdType -> Bool
isTopDmdType (DmdType DmdEnv
env [] DmdResult
res)
| DmdResult -> Bool
isTopRes DmdResult
res Bool -> Bool -> Bool
&& DmdEnv -> Bool
forall a. VarEnv a -> Bool
isEmptyVarEnv DmdEnv
env = Bool
True
isTopDmdType DmdType
_ = Bool
False
mkDmdType :: DmdEnv -> [Demand] -> DmdResult -> DmdType
mkDmdType :: DmdEnv -> [Demand] -> DmdResult -> DmdType
mkDmdType DmdEnv
fv [Demand]
ds DmdResult
res = DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
fv [Demand]
ds DmdResult
res
dmdTypeDepth :: DmdType -> Arity
dmdTypeDepth :: DmdType -> Int
dmdTypeDepth (DmdType DmdEnv
_ [Demand]
ds DmdResult
_) = [Demand] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Demand]
ds
removeDmdTyArgs :: DmdType -> DmdType
removeDmdTyArgs :: DmdType -> DmdType
removeDmdTyArgs = Int -> DmdType -> DmdType
ensureArgs Int
0
ensureArgs :: Arity -> DmdType -> DmdType
ensureArgs :: Int -> DmdType -> DmdType
ensureArgs Int
n DmdType
d | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
depth = DmdType
d
| Bool
otherwise = DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
fv [Demand]
ds' DmdResult
r'
where depth :: Int
depth = DmdType -> Int
dmdTypeDepth DmdType
d
DmdType DmdEnv
fv [Demand]
ds DmdResult
r = DmdType
d
ds' :: [Demand]
ds' = Int -> [Demand] -> [Demand]
forall a. Int -> [a] -> [a]
take Int
n ([Demand]
ds [Demand] -> [Demand] -> [Demand]
forall a. [a] -> [a] -> [a]
++ Demand -> [Demand]
forall a. a -> [a]
repeat (DmdResult -> Demand
forall r. Termination r -> Demand
resTypeArgDmd DmdResult
r))
r' :: DmdResult
r' = case DmdResult
r of
Dunno CPRResult
_ -> DmdResult
topRes
DmdResult
_ -> DmdResult
r
seqDmdType :: DmdType -> ()
seqDmdType :: DmdType -> ()
seqDmdType (DmdType DmdEnv
env [Demand]
ds DmdResult
res) =
DmdEnv -> ()
seqDmdEnv DmdEnv
env () -> () -> ()
`seq` [Demand] -> ()
seqDemandList [Demand]
ds () -> () -> ()
`seq` DmdResult -> ()
seqDmdResult DmdResult
res () -> () -> ()
`seq` ()
seqDmdEnv :: DmdEnv -> ()
seqDmdEnv :: DmdEnv -> ()
seqDmdEnv DmdEnv
env = ([Demand] -> ()) -> DmdEnv -> ()
forall elt. ([elt] -> ()) -> UniqFM elt -> ()
seqEltsUFM [Demand] -> ()
seqDemandList DmdEnv
env
splitDmdTy :: DmdType -> (Demand, DmdType)
splitDmdTy :: DmdType -> (Demand, DmdType)
splitDmdTy (DmdType DmdEnv
fv (Demand
dmd:[Demand]
dmds) DmdResult
res_ty) = (Demand
dmd, DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
fv [Demand]
dmds DmdResult
res_ty)
splitDmdTy ty :: DmdType
ty@(DmdType DmdEnv
_ [] DmdResult
res_ty) = (DmdResult -> Demand
forall r. Termination r -> Demand
resTypeArgDmd DmdResult
res_ty, DmdType
ty)
deferAfterIO :: DmdType -> DmdType
deferAfterIO :: DmdType -> DmdType
deferAfterIO d :: DmdType
d@(DmdType DmdEnv
_ [Demand]
_ DmdResult
res) =
case DmdType
d DmdType -> DmdType -> DmdType
`lubDmdType` DmdType
nopDmdType of
DmdType DmdEnv
fv [Demand]
ds DmdResult
_ -> DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
fv [Demand]
ds (DmdResult -> DmdResult
defer_res DmdResult
res)
where
defer_res :: DmdResult -> DmdResult
defer_res r :: DmdResult
r@(Dunno {}) = DmdResult
r
defer_res DmdResult
_ = DmdResult
topRes
strictenDmd :: Demand -> CleanDemand
strictenDmd :: Demand -> CleanDemand
strictenDmd (JD { sd :: forall s u. JointDmd s u -> s
sd = ArgStr
s, ud :: forall s u. JointDmd s u -> u
ud = ArgUse
u})
= JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: StrDmd
sd = ArgStr -> StrDmd
poke_s ArgStr
s, ud :: UseDmd
ud = ArgUse -> UseDmd
poke_u ArgUse
u }
where
poke_s :: ArgStr -> StrDmd
poke_s ArgStr
Lazy = StrDmd
HeadStr
poke_s (Str ExnStr
_ StrDmd
s) = StrDmd
s
poke_u :: ArgUse -> UseDmd
poke_u ArgUse
Abs = UseDmd
UHead
poke_u (Use Count
_ UseDmd
u) = UseDmd
u
type DmdShell
= JointDmd (Str ()) (Use ())
toCleanDmd :: Demand -> (DmdShell, CleanDemand)
toCleanDmd :: Demand -> (DmdShell, CleanDemand)
toCleanDmd (JD { sd :: forall s u. JointDmd s u -> s
sd = ArgStr
s, ud :: forall s u. JointDmd s u -> u
ud = ArgUse
u })
= (JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: Str ()
sd = Str ()
ss, ud :: Use ()
ud = Use ()
us }, JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: StrDmd
sd = StrDmd
s', ud :: UseDmd
ud = UseDmd
u' })
where
(Str ()
ss, StrDmd
s') = case ArgStr
s of
Str ExnStr
x StrDmd
s' -> (ExnStr -> () -> Str ()
forall s. ExnStr -> s -> Str s
Str ExnStr
x (), StrDmd
s')
ArgStr
Lazy -> (Str ()
forall s. Str s
Lazy, StrDmd
HeadStr)
(Use ()
us, UseDmd
u') = case ArgUse
u of
Use Count
c UseDmd
u' -> (Count -> () -> Use ()
forall u. Count -> u -> Use u
Use Count
c (), UseDmd
u')
ArgUse
Abs -> (Use ()
forall u. Use u
Abs, UseDmd
Used)
postProcessDmdType :: DmdShell -> DmdType -> BothDmdArg
postProcessDmdType :: DmdShell -> DmdType -> BothDmdArg
postProcessDmdType du :: DmdShell
du@(JD { sd :: forall s u. JointDmd s u -> s
sd = Str ()
ss }) (DmdType DmdEnv
fv [Demand]
_ DmdResult
res_ty)
= (DmdShell -> DmdEnv -> DmdEnv
postProcessDmdEnv DmdShell
du DmdEnv
fv, Termination ()
term_info)
where
term_info :: Termination ()
term_info = case Str () -> DmdResult -> DmdResult
postProcessDmdResult Str ()
ss DmdResult
res_ty of
Dunno CPRResult
_ -> () -> Termination ()
forall r. r -> Termination r
Dunno ()
DmdResult
ThrowsExn -> Termination ()
forall r. Termination r
ThrowsExn
DmdResult
Diverges -> Termination ()
forall r. Termination r
Diverges
postProcessDmdResult :: Str () -> DmdResult -> DmdResult
postProcessDmdResult :: Str () -> DmdResult -> DmdResult
postProcessDmdResult Str ()
Lazy DmdResult
_ = DmdResult
topRes
postProcessDmdResult (Str ExnStr
ExnStr ()
_) DmdResult
ThrowsExn = DmdResult
topRes
postProcessDmdResult Str ()
_ DmdResult
res = DmdResult
res
postProcessDmdEnv :: DmdShell -> DmdEnv -> DmdEnv
postProcessDmdEnv :: DmdShell -> DmdEnv -> DmdEnv
postProcessDmdEnv ds :: DmdShell
ds@(JD { sd :: forall s u. JointDmd s u -> s
sd = Str ()
ss, ud :: forall s u. JointDmd s u -> u
ud = Use ()
us }) DmdEnv
env
| Use ()
Abs <- Use ()
us = DmdEnv
emptyDmdEnv
| Str ExnStr
VanStr ()
_ <- Str ()
ss
, Use Count
One ()
_ <- Use ()
us = DmdEnv
env
| Bool
otherwise = (Demand -> Demand) -> DmdEnv -> DmdEnv
forall a b. (a -> b) -> VarEnv a -> VarEnv b
mapVarEnv (DmdShell -> Demand -> Demand
postProcessDmd DmdShell
ds) DmdEnv
env
reuseEnv :: DmdEnv -> DmdEnv
reuseEnv :: DmdEnv -> DmdEnv
reuseEnv = (Demand -> Demand) -> DmdEnv -> DmdEnv
forall a b. (a -> b) -> VarEnv a -> VarEnv b
mapVarEnv (DmdShell -> Demand -> Demand
postProcessDmd
(JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: Str ()
sd = ExnStr -> () -> Str ()
forall s. ExnStr -> s -> Str s
Str ExnStr
VanStr (), ud :: Use ()
ud = Count -> () -> Use ()
forall u. Count -> u -> Use u
Use Count
Many () }))
postProcessUnsat :: DmdShell -> DmdType -> DmdType
postProcessUnsat :: DmdShell -> DmdType -> DmdType
postProcessUnsat ds :: DmdShell
ds@(JD { sd :: forall s u. JointDmd s u -> s
sd = Str ()
ss }) (DmdType DmdEnv
fv [Demand]
args DmdResult
res_ty)
= DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType (DmdShell -> DmdEnv -> DmdEnv
postProcessDmdEnv DmdShell
ds DmdEnv
fv)
((Demand -> Demand) -> [Demand] -> [Demand]
forall a b. (a -> b) -> [a] -> [b]
map (DmdShell -> Demand -> Demand
postProcessDmd DmdShell
ds) [Demand]
args)
(Str () -> DmdResult -> DmdResult
postProcessDmdResult Str ()
ss DmdResult
res_ty)
postProcessDmd :: DmdShell -> Demand -> Demand
postProcessDmd :: DmdShell -> Demand -> Demand
postProcessDmd (JD { sd :: forall s u. JointDmd s u -> s
sd = Str ()
ss, ud :: forall s u. JointDmd s u -> u
ud = Use ()
us }) (JD { sd :: forall s u. JointDmd s u -> s
sd = ArgStr
s, ud :: forall s u. JointDmd s u -> u
ud = ArgUse
a})
= JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: ArgStr
sd = ArgStr
s', ud :: ArgUse
ud = ArgUse
a' }
where
s' :: ArgStr
s' = case Str ()
ss of
Str ()
Lazy -> ArgStr
forall s. Str s
Lazy
Str ExnStr
ExnStr ()
_ -> ArgStr -> ArgStr
markExnStr ArgStr
s
Str ExnStr
VanStr ()
_ -> ArgStr
s
a' :: ArgUse
a' = case Use ()
us of
Use ()
Abs -> ArgUse
forall u. Use u
Abs
Use Count
Many ()
_ -> ArgUse -> ArgUse
markReusedDmd ArgUse
a
Use Count
One ()
_ -> ArgUse
a
markExnStr :: ArgStr -> ArgStr
markExnStr :: ArgStr -> ArgStr
markExnStr (Str ExnStr
VanStr StrDmd
s) = ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str ExnStr
ExnStr StrDmd
s
markExnStr ArgStr
s = ArgStr
s
peelCallDmd :: CleanDemand -> (CleanDemand, DmdShell)
peelCallDmd :: CleanDemand -> (CleanDemand, DmdShell)
peelCallDmd (JD {sd :: forall s u. JointDmd s u -> s
sd = StrDmd
s, ud :: forall s u. JointDmd s u -> u
ud = UseDmd
u})
= (JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: StrDmd
sd = StrDmd
s', ud :: UseDmd
ud = UseDmd
u' }, JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: Str ()
sd = Str ()
ss, ud :: Use ()
ud = Use ()
us })
where
(StrDmd
s', Str ()
ss) = case StrDmd
s of
SCall StrDmd
s' -> (StrDmd
s', ExnStr -> () -> Str ()
forall s. ExnStr -> s -> Str s
Str ExnStr
VanStr ())
StrDmd
HyperStr -> (StrDmd
HyperStr, ExnStr -> () -> Str ()
forall s. ExnStr -> s -> Str s
Str ExnStr
VanStr ())
StrDmd
_ -> (StrDmd
HeadStr, Str ()
forall s. Str s
Lazy)
(UseDmd
u', Use ()
us) = case UseDmd
u of
UCall Count
c UseDmd
u' -> (UseDmd
u', Count -> () -> Use ()
forall u. Count -> u -> Use u
Use Count
c ())
UseDmd
_ -> (UseDmd
Used, Count -> () -> Use ()
forall u. Count -> u -> Use u
Use Count
Many ())
peelManyCalls :: Int -> CleanDemand -> DmdShell
peelManyCalls :: Int -> CleanDemand -> DmdShell
peelManyCalls Int
n (JD { sd :: forall s u. JointDmd s u -> s
sd = StrDmd
str, ud :: forall s u. JointDmd s u -> u
ud = UseDmd
abs })
= JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: Str ()
sd = Int -> StrDmd -> Str ()
go_str Int
n StrDmd
str, ud :: Use ()
ud = Int -> UseDmd -> Use ()
go_abs Int
n UseDmd
abs }
where
go_str :: Int -> StrDmd -> Str ()
go_str :: Int -> StrDmd -> Str ()
go_str Int
0 StrDmd
_ = ExnStr -> () -> Str ()
forall s. ExnStr -> s -> Str s
Str ExnStr
VanStr ()
go_str Int
_ StrDmd
HyperStr = ExnStr -> () -> Str ()
forall s. ExnStr -> s -> Str s
Str ExnStr
VanStr ()
go_str Int
n (SCall StrDmd
d') = Int -> StrDmd -> Str ()
go_str (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) StrDmd
d'
go_str Int
_ StrDmd
_ = Str ()
forall s. Str s
Lazy
go_abs :: Int -> UseDmd -> Use ()
go_abs :: Int -> UseDmd -> Use ()
go_abs Int
0 UseDmd
_ = Count -> () -> Use ()
forall u. Count -> u -> Use u
Use Count
One ()
go_abs Int
n (UCall Count
One UseDmd
d') = Int -> UseDmd -> Use ()
go_abs (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) UseDmd
d'
go_abs Int
_ UseDmd
_ = Count -> () -> Use ()
forall u. Count -> u -> Use u
Use Count
Many ()
peelFV :: DmdType -> Var -> (DmdType, Demand)
peelFV :: DmdType -> Var -> (DmdType, Demand)
peelFV (DmdType DmdEnv
fv [Demand]
ds DmdResult
res) Var
id =
(DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
fv' [Demand]
ds DmdResult
res, Demand
dmd)
where
fv' :: DmdEnv
fv' = DmdEnv
fv DmdEnv -> Var -> DmdEnv
forall a. VarEnv a -> Var -> VarEnv a
`delVarEnv` Var
id
dmd :: Demand
dmd = DmdEnv -> Var -> Maybe Demand
forall a. VarEnv a -> Var -> Maybe a
lookupVarEnv DmdEnv
fv Var
id Maybe Demand -> Demand -> Demand
forall a. Maybe a -> a -> a
`orElse` DmdResult -> Demand
forall r. Termination r -> Demand
defaultDmd DmdResult
res
addDemand :: Demand -> DmdType -> DmdType
addDemand :: Demand -> DmdType -> DmdType
addDemand Demand
dmd (DmdType DmdEnv
fv [Demand]
ds DmdResult
res) = DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
fv (Demand
dmdDemand -> [Demand] -> [Demand]
forall a. a -> [a] -> [a]
:[Demand]
ds) DmdResult
res
findIdDemand :: DmdType -> Var -> Demand
findIdDemand :: DmdType -> Var -> Demand
findIdDemand (DmdType DmdEnv
fv [Demand]
_ DmdResult
res) Var
id
= DmdEnv -> Var -> Maybe Demand
forall a. VarEnv a -> Var -> Maybe a
lookupVarEnv DmdEnv
fv Var
id Maybe Demand -> Demand -> Demand
forall a. Maybe a -> a -> a
`orElse` DmdResult -> Demand
forall r. Termination r -> Demand
defaultDmd DmdResult
res
newtype StrictSig = StrictSig DmdType
deriving( StrictSig -> StrictSig -> Bool
(StrictSig -> StrictSig -> Bool)
-> (StrictSig -> StrictSig -> Bool) -> Eq StrictSig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StrictSig -> StrictSig -> Bool
$c/= :: StrictSig -> StrictSig -> Bool
== :: StrictSig -> StrictSig -> Bool
$c== :: StrictSig -> StrictSig -> Bool
Eq )
instance Outputable StrictSig where
ppr :: StrictSig -> SDoc
ppr (StrictSig DmdType
ty) = DmdType -> SDoc
forall a. Outputable a => a -> SDoc
ppr DmdType
ty
pprIfaceStrictSig :: StrictSig -> SDoc
pprIfaceStrictSig :: StrictSig -> SDoc
pprIfaceStrictSig (StrictSig (DmdType DmdEnv
_ [Demand]
dmds DmdResult
res))
= [SDoc] -> SDoc
hcat ((Demand -> SDoc) -> [Demand] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Demand -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Demand]
dmds) SDoc -> SDoc -> SDoc
<> DmdResult -> SDoc
forall a. Outputable a => a -> SDoc
ppr DmdResult
res
mkStrictSig :: DmdType -> StrictSig
mkStrictSig :: DmdType -> StrictSig
mkStrictSig DmdType
dmd_ty = DmdType -> StrictSig
StrictSig DmdType
dmd_ty
mkClosedStrictSig :: [Demand] -> DmdResult -> StrictSig
mkClosedStrictSig :: [Demand] -> DmdResult -> StrictSig
mkClosedStrictSig [Demand]
ds DmdResult
res = DmdType -> StrictSig
mkStrictSig (DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
emptyDmdEnv [Demand]
ds DmdResult
res)
splitStrictSig :: StrictSig -> ([Demand], DmdResult)
splitStrictSig :: StrictSig -> ([Demand], DmdResult)
splitStrictSig (StrictSig (DmdType DmdEnv
_ [Demand]
dmds DmdResult
res)) = ([Demand]
dmds, DmdResult
res)
increaseStrictSigArity :: Int -> StrictSig -> StrictSig
increaseStrictSigArity :: Int -> StrictSig -> StrictSig
increaseStrictSigArity Int
arity_increase sig :: StrictSig
sig@(StrictSig dmd_ty :: DmdType
dmd_ty@(DmdType DmdEnv
env [Demand]
dmds DmdResult
res))
| DmdType -> Bool
isTopDmdType DmdType
dmd_ty = StrictSig
sig
| Int
arity_increase Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = StrictSig
sig
| Bool
otherwise = DmdType -> StrictSig
StrictSig (DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
env [Demand]
dmds' DmdResult
res)
where
dmds' :: [Demand]
dmds' = Int -> Demand -> [Demand]
forall a. Int -> a -> [a]
replicate Int
arity_increase Demand
topDmd [Demand] -> [Demand] -> [Demand]
forall a. [a] -> [a] -> [a]
++ [Demand]
dmds
etaExpandStrictSig :: Arity -> StrictSig -> StrictSig
etaExpandStrictSig :: Int -> StrictSig -> StrictSig
etaExpandStrictSig Int
arity sig :: StrictSig
sig@(StrictSig dmd_ty :: DmdType
dmd_ty@(DmdType DmdEnv
env [Demand]
dmds DmdResult
res))
| DmdType -> Bool
isTopDmdType DmdType
dmd_ty = StrictSig
sig
| Int
arity_increase Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = StrictSig
sig
| Bool
otherwise = DmdType -> StrictSig
StrictSig (DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
env [Demand]
dmds' DmdResult
res)
where
arity_increase :: Int
arity_increase = Int
arity Int -> Int -> Int
forall a. Num a => a -> a -> a
- [Demand] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Demand]
dmds
dmds' :: [Demand]
dmds' = [Demand]
dmds [Demand] -> [Demand] -> [Demand]
forall a. [a] -> [a] -> [a]
++ Int -> Demand -> [Demand]
forall a. Int -> a -> [a]
replicate Int
arity_increase Demand
topDmd
isTopSig :: StrictSig -> Bool
isTopSig :: StrictSig -> Bool
isTopSig (StrictSig DmdType
ty) = DmdType -> Bool
isTopDmdType DmdType
ty
hasDemandEnvSig :: StrictSig -> Bool
hasDemandEnvSig :: StrictSig -> Bool
hasDemandEnvSig (StrictSig (DmdType DmdEnv
env [Demand]
_ DmdResult
_)) = Bool -> Bool
not (DmdEnv -> Bool
forall a. VarEnv a -> Bool
isEmptyVarEnv DmdEnv
env)
strictSigDmdEnv :: StrictSig -> DmdEnv
strictSigDmdEnv :: StrictSig -> DmdEnv
strictSigDmdEnv (StrictSig (DmdType DmdEnv
env [Demand]
_ DmdResult
_)) = DmdEnv
env
isBottomingSig :: StrictSig -> Bool
isBottomingSig :: StrictSig -> Bool
isBottomingSig (StrictSig (DmdType DmdEnv
_ [Demand]
_ DmdResult
res)) = DmdResult -> Bool
isBotRes DmdResult
res
nopSig, botSig, exnSig :: StrictSig
nopSig :: StrictSig
nopSig = DmdType -> StrictSig
StrictSig DmdType
nopDmdType
botSig :: StrictSig
botSig = DmdType -> StrictSig
StrictSig DmdType
botDmdType
exnSig :: StrictSig
exnSig = DmdType -> StrictSig
StrictSig DmdType
exnDmdType
cprProdSig :: Arity -> StrictSig
cprProdSig :: Int -> StrictSig
cprProdSig Int
arity = DmdType -> StrictSig
StrictSig (Int -> DmdType
cprProdDmdType Int
arity)
seqStrictSig :: StrictSig -> ()
seqStrictSig :: StrictSig -> ()
seqStrictSig (StrictSig DmdType
ty) = DmdType -> ()
seqDmdType DmdType
ty
dmdTransformSig :: StrictSig -> CleanDemand -> DmdType
dmdTransformSig :: StrictSig -> CleanDemand -> DmdType
dmdTransformSig (StrictSig dmd_ty :: DmdType
dmd_ty@(DmdType DmdEnv
_ [Demand]
arg_ds DmdResult
_)) CleanDemand
cd
= DmdShell -> DmdType -> DmdType
postProcessUnsat (Int -> CleanDemand -> DmdShell
peelManyCalls ([Demand] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Demand]
arg_ds) CleanDemand
cd) DmdType
dmd_ty
dmdTransformDataConSig :: Arity -> StrictSig -> CleanDemand -> DmdType
dmdTransformDataConSig :: Int -> StrictSig -> CleanDemand -> DmdType
dmdTransformDataConSig Int
arity (StrictSig (DmdType DmdEnv
_ [Demand]
_ DmdResult
con_res))
(JD { sd :: forall s u. JointDmd s u -> s
sd = StrDmd
str, ud :: forall s u. JointDmd s u -> u
ud = UseDmd
abs })
| Just [ArgStr]
str_dmds <- Int -> StrDmd -> Maybe [ArgStr]
forall a. (Eq a, Num a) => a -> StrDmd -> Maybe [ArgStr]
go_str Int
arity StrDmd
str
, Just [ArgUse]
abs_dmds <- Int -> UseDmd -> Maybe [ArgUse]
forall t. (Eq t, Num t) => t -> UseDmd -> Maybe [ArgUse]
go_abs Int
arity UseDmd
abs
= DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
emptyDmdEnv ([ArgStr] -> [ArgUse] -> [Demand]
forall s u. [s] -> [u] -> [JointDmd s u]
mkJointDmds [ArgStr]
str_dmds [ArgUse]
abs_dmds) DmdResult
con_res
| Bool
otherwise
= DmdType
nopDmdType
where
go_str :: a -> StrDmd -> Maybe [ArgStr]
go_str a
0 StrDmd
dmd = Int -> StrDmd -> Maybe [ArgStr]
splitStrProdDmd Int
arity StrDmd
dmd
go_str a
n (SCall StrDmd
s') = a -> StrDmd -> Maybe [ArgStr]
go_str (a
na -> a -> a
forall a. Num a => a -> a -> a
-a
1) StrDmd
s'
go_str a
n StrDmd
HyperStr = a -> StrDmd -> Maybe [ArgStr]
go_str (a
na -> a -> a
forall a. Num a => a -> a -> a
-a
1) StrDmd
HyperStr
go_str a
_ StrDmd
_ = Maybe [ArgStr]
forall a. Maybe a
Nothing
go_abs :: t -> UseDmd -> Maybe [ArgUse]
go_abs t
0 UseDmd
dmd = Int -> UseDmd -> Maybe [ArgUse]
splitUseProdDmd Int
arity UseDmd
dmd
go_abs t
n (UCall Count
One UseDmd
u') = t -> UseDmd -> Maybe [ArgUse]
go_abs (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1) UseDmd
u'
go_abs t
_ UseDmd
_ = Maybe [ArgUse]
forall a. Maybe a
Nothing
dmdTransformDictSelSig :: StrictSig -> CleanDemand -> DmdType
dmdTransformDictSelSig :: StrictSig -> CleanDemand -> DmdType
dmdTransformDictSelSig (StrictSig (DmdType DmdEnv
_ [Demand
dict_dmd] DmdResult
_)) CleanDemand
cd
| (CleanDemand
cd',DmdShell
defer_use) <- CleanDemand -> (CleanDemand, DmdShell)
peelCallDmd CleanDemand
cd
, Just [Demand]
jds <- Demand -> Maybe [Demand]
splitProdDmd_maybe Demand
dict_dmd
= DmdShell -> DmdType -> DmdType
postProcessUnsat DmdShell
defer_use (DmdType -> DmdType) -> DmdType -> DmdType
forall a b. (a -> b) -> a -> b
$
DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
emptyDmdEnv [CleanDemand -> Demand
mkOnceUsedDmd (CleanDemand -> Demand) -> CleanDemand -> Demand
forall a b. (a -> b) -> a -> b
$ [Demand] -> CleanDemand
mkProdDmd ([Demand] -> CleanDemand) -> [Demand] -> CleanDemand
forall a b. (a -> b) -> a -> b
$ (Demand -> Demand) -> [Demand] -> [Demand]
forall a b. (a -> b) -> [a] -> [b]
map (CleanDemand -> Demand -> Demand
enhance CleanDemand
cd') [Demand]
jds] DmdResult
topRes
| Bool
otherwise
= DmdType
nopDmdType
where
enhance :: CleanDemand -> Demand -> Demand
enhance CleanDemand
cd Demand
old | Demand -> Bool
forall s u. JointDmd (Str s) (Use u) -> Bool
isAbsDmd Demand
old = Demand
old
| Bool
otherwise = CleanDemand -> Demand
mkOnceUsedDmd CleanDemand
cd
dmdTransformDictSelSig StrictSig
_ CleanDemand
_ = String -> DmdType
forall a. String -> a
panic String
"dmdTransformDictSelSig: no args"
argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]]
argsOneShots :: StrictSig -> Int -> [[OneShotInfo]]
argsOneShots (StrictSig (DmdType DmdEnv
_ [Demand]
arg_ds DmdResult
_)) Int
n_val_args
| Bool
unsaturated_call = []
| Bool
otherwise = [Demand] -> [[OneShotInfo]]
go [Demand]
arg_ds
where
unsaturated_call :: Bool
unsaturated_call = [Demand]
arg_ds [Demand] -> Int -> Bool
forall a. [a] -> Int -> Bool
`lengthExceeds` Int
n_val_args
go :: [Demand] -> [[OneShotInfo]]
go [] = []
go (Demand
arg_d : [Demand]
arg_ds) = Demand -> [OneShotInfo]
argOneShots Demand
arg_d [OneShotInfo] -> [[OneShotInfo]] -> [[OneShotInfo]]
forall a. [a] -> [[a]] -> [[a]]
`cons` [Demand] -> [[OneShotInfo]]
go [Demand]
arg_ds
cons :: [a] -> [[a]] -> [[a]]
cons [] [] = []
cons [a]
a [[a]]
as = [a]
a[a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
:[[a]]
as
saturatedByOneShots :: Int -> Demand -> Bool
saturatedByOneShots :: Int -> Demand -> Bool
saturatedByOneShots Int
n (JD { ud :: forall s u. JointDmd s u -> u
ud = ArgUse
usg })
= case ArgUse
usg of
Use Count
_ UseDmd
arg_usg -> Int -> UseDmd -> Bool
forall t. (Eq t, Num t) => t -> UseDmd -> Bool
go Int
n UseDmd
arg_usg
ArgUse
_ -> Bool
False
where
go :: t -> UseDmd -> Bool
go t
0 UseDmd
_ = Bool
True
go t
n (UCall Count
One UseDmd
u) = t -> UseDmd -> Bool
go (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1) UseDmd
u
go t
_ UseDmd
_ = Bool
False
argOneShots :: Demand
-> [OneShotInfo]
argOneShots :: Demand -> [OneShotInfo]
argOneShots (JD { ud :: forall s u. JointDmd s u -> u
ud = ArgUse
usg })
= case ArgUse
usg of
Use Count
_ UseDmd
arg_usg -> UseDmd -> [OneShotInfo]
go UseDmd
arg_usg
ArgUse
_ -> []
where
go :: UseDmd -> [OneShotInfo]
go (UCall Count
One UseDmd
u) = OneShotInfo
OneShotLam OneShotInfo -> [OneShotInfo] -> [OneShotInfo]
forall a. a -> [a] -> [a]
: UseDmd -> [OneShotInfo]
go UseDmd
u
go (UCall Count
Many UseDmd
u) = OneShotInfo
NoOneShotInfo OneShotInfo -> [OneShotInfo] -> [OneShotInfo]
forall a. a -> [a] -> [a]
: UseDmd -> [OneShotInfo]
go UseDmd
u
go UseDmd
_ = []
appIsBottom :: StrictSig -> Int -> Bool
appIsBottom :: StrictSig -> Int -> Bool
appIsBottom (StrictSig (DmdType DmdEnv
_ [Demand]
ds DmdResult
res)) Int
n
| DmdResult -> Bool
isBotRes DmdResult
res = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Demand] -> Int -> Bool
forall a. [a] -> Int -> Bool
lengthExceeds [Demand]
ds Int
n
appIsBottom StrictSig
_ Int
_ = Bool
False
zapUsageEnvSig :: StrictSig -> StrictSig
zapUsageEnvSig :: StrictSig -> StrictSig
zapUsageEnvSig (StrictSig (DmdType DmdEnv
_ [Demand]
ds DmdResult
r)) = [Demand] -> DmdResult -> StrictSig
mkClosedStrictSig [Demand]
ds DmdResult
r
zapUsageDemand :: Demand -> Demand
zapUsageDemand :: Demand -> Demand
zapUsageDemand = KillFlags -> Demand -> Demand
kill_usage (KillFlags -> Demand -> Demand) -> KillFlags -> Demand -> Demand
forall a b. (a -> b) -> a -> b
$ KillFlags :: Bool -> Bool -> Bool -> KillFlags
KillFlags
{ kf_abs :: Bool
kf_abs = Bool
True
, kf_used_once :: Bool
kf_used_once = Bool
True
, kf_called_once :: Bool
kf_called_once = Bool
True
}
zapUsedOnceDemand :: Demand -> Demand
zapUsedOnceDemand :: Demand -> Demand
zapUsedOnceDemand = KillFlags -> Demand -> Demand
kill_usage (KillFlags -> Demand -> Demand) -> KillFlags -> Demand -> Demand
forall a b. (a -> b) -> a -> b
$ KillFlags :: Bool -> Bool -> Bool -> KillFlags
KillFlags
{ kf_abs :: Bool
kf_abs = Bool
False
, kf_used_once :: Bool
kf_used_once = Bool
True
, kf_called_once :: Bool
kf_called_once = Bool
False
}
zapUsedOnceSig :: StrictSig -> StrictSig
zapUsedOnceSig :: StrictSig -> StrictSig
zapUsedOnceSig (StrictSig (DmdType DmdEnv
env [Demand]
ds DmdResult
r))
= DmdType -> StrictSig
StrictSig (DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
env ((Demand -> Demand) -> [Demand] -> [Demand]
forall a b. (a -> b) -> [a] -> [b]
map Demand -> Demand
zapUsedOnceDemand [Demand]
ds) DmdResult
r)
killUsageDemand :: DynFlags -> Demand -> Demand
killUsageDemand :: DynFlags -> Demand -> Demand
killUsageDemand DynFlags
dflags Demand
dmd
| Just KillFlags
kfs <- DynFlags -> Maybe KillFlags
killFlags DynFlags
dflags = KillFlags -> Demand -> Demand
kill_usage KillFlags
kfs Demand
dmd
| Bool
otherwise = Demand
dmd
killUsageSig :: DynFlags -> StrictSig -> StrictSig
killUsageSig :: DynFlags -> StrictSig -> StrictSig
killUsageSig DynFlags
dflags sig :: StrictSig
sig@(StrictSig (DmdType DmdEnv
env [Demand]
ds DmdResult
r))
| Just KillFlags
kfs <- DynFlags -> Maybe KillFlags
killFlags DynFlags
dflags = DmdType -> StrictSig
StrictSig (DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
env ((Demand -> Demand) -> [Demand] -> [Demand]
forall a b. (a -> b) -> [a] -> [b]
map (KillFlags -> Demand -> Demand
kill_usage KillFlags
kfs) [Demand]
ds) DmdResult
r)
| Bool
otherwise = StrictSig
sig
data KillFlags = KillFlags
{ KillFlags -> Bool
kf_abs :: Bool
, KillFlags -> Bool
kf_used_once :: Bool
, KillFlags -> Bool
kf_called_once :: Bool
}
killFlags :: DynFlags -> Maybe KillFlags
killFlags :: DynFlags -> Maybe KillFlags
killFlags DynFlags
dflags
| Bool -> Bool
not Bool
kf_abs Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
kf_used_once = Maybe KillFlags
forall a. Maybe a
Nothing
| Bool
otherwise = KillFlags -> Maybe KillFlags
forall a. a -> Maybe a
Just (KillFlags :: Bool -> Bool -> Bool -> KillFlags
KillFlags {Bool
kf_called_once :: Bool
kf_used_once :: Bool
kf_abs :: Bool
kf_called_once :: Bool
kf_used_once :: Bool
kf_abs :: Bool
..})
where
kf_abs :: Bool
kf_abs = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KillAbsence DynFlags
dflags
kf_used_once :: Bool
kf_used_once = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KillOneShot DynFlags
dflags
kf_called_once :: Bool
kf_called_once = Bool
kf_used_once
kill_usage :: KillFlags -> Demand -> Demand
kill_usage :: KillFlags -> Demand -> Demand
kill_usage KillFlags
kfs (JD {sd :: forall s u. JointDmd s u -> s
sd = ArgStr
s, ud :: forall s u. JointDmd s u -> u
ud = ArgUse
u}) = JD :: forall s u. s -> u -> JointDmd s u
JD {sd :: ArgStr
sd = ArgStr
s, ud :: ArgUse
ud = KillFlags -> ArgUse -> ArgUse
zap_musg KillFlags
kfs ArgUse
u}
zap_musg :: KillFlags -> ArgUse -> ArgUse
zap_musg :: KillFlags -> ArgUse -> ArgUse
zap_musg KillFlags
kfs ArgUse
Abs
| KillFlags -> Bool
kf_abs KillFlags
kfs = ArgUse
useTop
| Bool
otherwise = ArgUse
forall u. Use u
Abs
zap_musg KillFlags
kfs (Use Count
c UseDmd
u)
| KillFlags -> Bool
kf_used_once KillFlags
kfs = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
Many (KillFlags -> UseDmd -> UseDmd
zap_usg KillFlags
kfs UseDmd
u)
| Bool
otherwise = Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
c (KillFlags -> UseDmd -> UseDmd
zap_usg KillFlags
kfs UseDmd
u)
zap_usg :: KillFlags -> UseDmd -> UseDmd
zap_usg :: KillFlags -> UseDmd -> UseDmd
zap_usg KillFlags
kfs (UCall Count
c UseDmd
u)
| KillFlags -> Bool
kf_called_once KillFlags
kfs = Count -> UseDmd -> UseDmd
UCall Count
Many (KillFlags -> UseDmd -> UseDmd
zap_usg KillFlags
kfs UseDmd
u)
| Bool
otherwise = Count -> UseDmd -> UseDmd
UCall Count
c (KillFlags -> UseDmd -> UseDmd
zap_usg KillFlags
kfs UseDmd
u)
zap_usg KillFlags
kfs (UProd [ArgUse]
us) = [ArgUse] -> UseDmd
UProd ((ArgUse -> ArgUse) -> [ArgUse] -> [ArgUse]
forall a b. (a -> b) -> [a] -> [b]
map (KillFlags -> ArgUse -> ArgUse
zap_musg KillFlags
kfs) [ArgUse]
us)
zap_usg KillFlags
_ UseDmd
u = UseDmd
u
strictifyDictDmd :: Type -> Demand -> Demand
strictifyDictDmd :: Type -> Demand -> Demand
strictifyDictDmd Type
ty Demand
dmd = case Demand -> ArgUse
forall s u. JointDmd s u -> u
getUseDmd Demand
dmd of
Use Count
n UseDmd
_ |
Just (TyCon
tycon, [Type]
_arg_tys, DataCon
_data_con, [Type]
inst_con_arg_tys)
<- Type -> Maybe (TyCon, [Type], DataCon, [Type])
splitDataProductType_maybe Type
ty,
Bool -> Bool
not (TyCon -> Bool
isNewTyCon TyCon
tycon), TyCon -> Bool
isClassTyCon TyCon
tycon
-> Demand
seqDmd Demand -> Demand -> Demand
`bothDmd`
case Demand -> Maybe [Demand]
splitProdDmd_maybe Demand
dmd of
Maybe [Demand]
Nothing -> Demand
dmd
Just [Demand]
dmds
| (Demand -> Bool) -> [Demand] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Bool -> Bool
not (Bool -> Bool) -> (Demand -> Bool) -> Demand -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Demand -> Bool
forall s u. JointDmd (Str s) (Use u) -> Bool
isAbsDmd) [Demand]
dmds -> Demand
evalDmd
| Bool
otherwise -> case [Demand] -> CleanDemand
mkProdDmd ([Demand] -> CleanDemand) -> [Demand] -> CleanDemand
forall a b. (a -> b) -> a -> b
$ (Type -> Demand -> Demand) -> [Type] -> [Demand] -> [Demand]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Type -> Demand -> Demand
strictifyDictDmd [Type]
inst_con_arg_tys [Demand]
dmds of
JD {sd :: forall s u. JointDmd s u -> s
sd = StrDmd
s,ud :: forall s u. JointDmd s u -> u
ud = UseDmd
a} -> ArgStr -> ArgUse -> Demand
forall s u. s -> u -> JointDmd s u
JD (ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str ExnStr
VanStr StrDmd
s) (Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
n UseDmd
a)
ArgUse
_ -> Demand
dmd
strictifyDmd :: Demand -> Demand
strictifyDmd :: Demand -> Demand
strictifyDmd dmd :: Demand
dmd@(JD { sd :: forall s u. JointDmd s u -> s
sd = ArgStr
str })
= Demand
dmd { sd :: ArgStr
sd = ArgStr
str ArgStr -> ArgStr -> ArgStr
`bothArgStr` ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str ExnStr
VanStr StrDmd
HeadStr }
instance Binary StrDmd where
put_ :: BinHandle -> StrDmd -> IO ()
put_ BinHandle
bh StrDmd
HyperStr = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh StrDmd
HeadStr = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
put_ BinHandle
bh (SCall StrDmd
s) = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
BinHandle -> StrDmd -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh StrDmd
s
put_ BinHandle
bh (SProd [ArgStr]
sx) = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
BinHandle -> [ArgStr] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [ArgStr]
sx
get :: BinHandle -> IO StrDmd
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> do StrDmd -> IO StrDmd
forall (m :: * -> *) a. Monad m => a -> m a
return StrDmd
HyperStr
Word8
1 -> do StrDmd -> IO StrDmd
forall (m :: * -> *) a. Monad m => a -> m a
return StrDmd
HeadStr
Word8
2 -> do StrDmd
s <- BinHandle -> IO StrDmd
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
StrDmd -> IO StrDmd
forall (m :: * -> *) a. Monad m => a -> m a
return (StrDmd -> StrDmd
SCall StrDmd
s)
Word8
_ -> do [ArgStr]
sx <- BinHandle -> IO [ArgStr]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
StrDmd -> IO StrDmd
forall (m :: * -> *) a. Monad m => a -> m a
return ([ArgStr] -> StrDmd
SProd [ArgStr]
sx)
instance Binary ExnStr where
put_ :: BinHandle -> ExnStr -> IO ()
put_ BinHandle
bh ExnStr
VanStr = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh ExnStr
ExnStr = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
get :: BinHandle -> IO ExnStr
get BinHandle
bh = do Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
ExnStr -> IO ExnStr
forall (m :: * -> *) a. Monad m => a -> m a
return (case Word8
h of
Word8
0 -> ExnStr
VanStr
Word8
_ -> ExnStr
ExnStr)
instance Binary ArgStr where
put_ :: BinHandle -> ArgStr -> IO ()
put_ BinHandle
bh ArgStr
Lazy = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh (Str ExnStr
x StrDmd
s) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
BinHandle -> ExnStr -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh ExnStr
x
BinHandle -> StrDmd -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh StrDmd
s
get :: BinHandle -> IO ArgStr
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> ArgStr -> IO ArgStr
forall (m :: * -> *) a. Monad m => a -> m a
return ArgStr
forall s. Str s
Lazy
Word8
_ -> do ExnStr
x <- BinHandle -> IO ExnStr
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
StrDmd
s <- BinHandle -> IO StrDmd
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
ArgStr -> IO ArgStr
forall (m :: * -> *) a. Monad m => a -> m a
return (ArgStr -> IO ArgStr) -> ArgStr -> IO ArgStr
forall a b. (a -> b) -> a -> b
$ ExnStr -> StrDmd -> ArgStr
forall s. ExnStr -> s -> Str s
Str ExnStr
x StrDmd
s
instance Binary Count where
put_ :: BinHandle -> Count -> IO ()
put_ BinHandle
bh Count
One = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh Count
Many = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
get :: BinHandle -> IO Count
get BinHandle
bh = do Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> Count -> IO Count
forall (m :: * -> *) a. Monad m => a -> m a
return Count
One
Word8
_ -> Count -> IO Count
forall (m :: * -> *) a. Monad m => a -> m a
return Count
Many
instance Binary ArgUse where
put_ :: BinHandle -> ArgUse -> IO ()
put_ BinHandle
bh ArgUse
Abs = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh (Use Count
c UseDmd
u) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
BinHandle -> Count -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Count
c
BinHandle -> UseDmd -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh UseDmd
u
get :: BinHandle -> IO ArgUse
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> ArgUse -> IO ArgUse
forall (m :: * -> *) a. Monad m => a -> m a
return ArgUse
forall u. Use u
Abs
Word8
_ -> do Count
c <- BinHandle -> IO Count
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
UseDmd
u <- BinHandle -> IO UseDmd
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
ArgUse -> IO ArgUse
forall (m :: * -> *) a. Monad m => a -> m a
return (ArgUse -> IO ArgUse) -> ArgUse -> IO ArgUse
forall a b. (a -> b) -> a -> b
$ Count -> UseDmd -> ArgUse
forall u. Count -> u -> Use u
Use Count
c UseDmd
u
instance Binary UseDmd where
put_ :: BinHandle -> UseDmd -> IO ()
put_ BinHandle
bh UseDmd
Used = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh UseDmd
UHead = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
put_ BinHandle
bh (UCall Count
c UseDmd
u) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
BinHandle -> Count -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Count
c
BinHandle -> UseDmd -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh UseDmd
u
put_ BinHandle
bh (UProd [ArgUse]
ux) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
BinHandle -> [ArgUse] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [ArgUse]
ux
get :: BinHandle -> IO UseDmd
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> UseDmd -> IO UseDmd
forall (m :: * -> *) a. Monad m => a -> m a
return (UseDmd -> IO UseDmd) -> UseDmd -> IO UseDmd
forall a b. (a -> b) -> a -> b
$ UseDmd
Used
Word8
1 -> UseDmd -> IO UseDmd
forall (m :: * -> *) a. Monad m => a -> m a
return (UseDmd -> IO UseDmd) -> UseDmd -> IO UseDmd
forall a b. (a -> b) -> a -> b
$ UseDmd
UHead
Word8
2 -> do Count
c <- BinHandle -> IO Count
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
UseDmd
u <- BinHandle -> IO UseDmd
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
UseDmd -> IO UseDmd
forall (m :: * -> *) a. Monad m => a -> m a
return (Count -> UseDmd -> UseDmd
UCall Count
c UseDmd
u)
Word8
_ -> do [ArgUse]
ux <- BinHandle -> IO [ArgUse]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
UseDmd -> IO UseDmd
forall (m :: * -> *) a. Monad m => a -> m a
return ([ArgUse] -> UseDmd
UProd [ArgUse]
ux)
instance (Binary s, Binary u) => Binary (JointDmd s u) where
put_ :: BinHandle -> JointDmd s u -> IO ()
put_ BinHandle
bh (JD { sd :: forall s u. JointDmd s u -> s
sd = s
x, ud :: forall s u. JointDmd s u -> u
ud = u
y }) = do BinHandle -> s -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh s
x; BinHandle -> u -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh u
y
get :: BinHandle -> IO (JointDmd s u)
get BinHandle
bh = do
s
x <- BinHandle -> IO s
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
u
y <- BinHandle -> IO u
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
JointDmd s u -> IO (JointDmd s u)
forall (m :: * -> *) a. Monad m => a -> m a
return (JointDmd s u -> IO (JointDmd s u))
-> JointDmd s u -> IO (JointDmd s u)
forall a b. (a -> b) -> a -> b
$ JD :: forall s u. s -> u -> JointDmd s u
JD { sd :: s
sd = s
x, ud :: u
ud = u
y }
instance Binary StrictSig where
put_ :: BinHandle -> StrictSig -> IO ()
put_ BinHandle
bh (StrictSig DmdType
aa) = do
BinHandle -> DmdType -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh DmdType
aa
get :: BinHandle -> IO StrictSig
get BinHandle
bh = do
DmdType
aa <- BinHandle -> IO DmdType
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
StrictSig -> IO StrictSig
forall (m :: * -> *) a. Monad m => a -> m a
return (DmdType -> StrictSig
StrictSig DmdType
aa)
instance Binary DmdType where
put_ :: BinHandle -> DmdType -> IO ()
put_ BinHandle
bh (DmdType DmdEnv
_ [Demand]
ds DmdResult
dr)
= do BinHandle -> [Demand] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Demand]
ds
BinHandle -> DmdResult -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh DmdResult
dr
get :: BinHandle -> IO DmdType
get BinHandle
bh
= do [Demand]
ds <- BinHandle -> IO [Demand]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
DmdResult
dr <- BinHandle -> IO DmdResult
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
DmdType -> IO DmdType
forall (m :: * -> *) a. Monad m => a -> m a
return (DmdEnv -> [Demand] -> DmdResult -> DmdType
DmdType DmdEnv
emptyDmdEnv [Demand]
ds DmdResult
dr)
instance Binary DmdResult where
put_ :: BinHandle -> DmdResult -> IO ()
put_ BinHandle
bh (Dunno CPRResult
c) = do { BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0; BinHandle -> CPRResult -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh CPRResult
c }
put_ BinHandle
bh DmdResult
ThrowsExn = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
put_ BinHandle
bh DmdResult
Diverges = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
get :: BinHandle -> IO DmdResult
get BinHandle
bh = do { Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
; case Word8
h of
Word8
0 -> do { CPRResult
c <- BinHandle -> IO CPRResult
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh; DmdResult -> IO DmdResult
forall (m :: * -> *) a. Monad m => a -> m a
return (CPRResult -> DmdResult
forall r. r -> Termination r
Dunno CPRResult
c) }
Word8
1 -> DmdResult -> IO DmdResult
forall (m :: * -> *) a. Monad m => a -> m a
return DmdResult
forall r. Termination r
ThrowsExn
Word8
_ -> DmdResult -> IO DmdResult
forall (m :: * -> *) a. Monad m => a -> m a
return DmdResult
forall r. Termination r
Diverges }
instance Binary CPRResult where
put_ :: BinHandle -> CPRResult -> IO ()
put_ BinHandle
bh (RetSum Int
n) = do { BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0; BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
n }
put_ BinHandle
bh CPRResult
RetProd = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
put_ BinHandle
bh CPRResult
NoCPR = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
get :: BinHandle -> IO CPRResult
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> do { Int
n <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh; CPRResult -> IO CPRResult
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> CPRResult
RetSum Int
n) }
Word8
1 -> CPRResult -> IO CPRResult
forall (m :: * -> *) a. Monad m => a -> m a
return CPRResult
RetProd
Word8
_ -> CPRResult -> IO CPRResult
forall (m :: * -> *) a. Monad m => a -> m a
return CPRResult
NoCPR