{-# LANGUAGE CPP #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module GHC.Types.Demand (
Card(..), Demand(..), SubDemand(Prod), mkProd, viewProd,
absDmd, topDmd, botDmd, seqDmd, topSubDmd,
lubCard, lubDmd, lubSubDmd,
plusCard, plusDmd, plusSubDmd,
multCard, multDmd, multSubDmd,
isAbs, isUsedOnce, isStrict,
isAbsDmd, isUsedOnceDmd, isStrUsedDmd, isStrictDmd,
isTopDmd, isSeqDmd, isWeakDmd,
evalDmd,
lazyApply1Dmd, lazyApply2Dmd, strictOnceApply1Dmd, strictManyApply1Dmd,
oneifyCard, oneifyDmd, strictifyDmd, strictifyDictDmd, mkWorkerDemand,
peelCallDmd, peelManyCalls, mkCalledOnceDmd, mkCalledOnceDmds,
addCaseBndrDmd,
argOneShots, argsOneShots, saturatedByOneShots,
DmdEnv, emptyDmdEnv,
keepAliveDmdEnv, reuseEnv,
Divergence(..), topDiv, botDiv, exnDiv, lubDivergence, isDeadEndDiv,
DmdType(..), dmdTypeDepth,
nopDmdType, botDmdType,
lubDmdType, plusDmdType, multDmdType,
PlusDmdArg, mkPlusDmdArg, toPlusDmdArg,
peelFV, findIdDemand, addDemand, splitDmdTy, deferAfterPreciseException,
keepAliveDmdType,
StrictSig(..), mkStrictSigForArity, mkClosedStrictSig,
splitStrictSig, strictSigDmdEnv, hasDemandEnvSig,
nopSig, botSig, isTopSig, isDeadEndSig, appIsDeadEnd,
prependArgsStrictSig, etaConvertStrictSig,
DmdTransformer, dmdTransformSig, dmdTransformDataConSig, dmdTransformDictSelSig,
TypeShape(..), trimToType,
seqDemand, seqDemandList, seqDmdType, seqStrictSig,
zapUsageDemand, zapDmdEnvSig, zapUsedOnceDemand, zapUsedOnceSig
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Types.Var ( Var, Id )
import GHC.Types.Var.Env
import GHC.Types.Var.Set
import GHC.Types.Unique.FM
import GHC.Types.Basic
import GHC.Data.Maybe ( orElse )
import GHC.Core.Type ( Type )
import GHC.Core.TyCon ( isNewTyCon, isClassTyCon )
import GHC.Core.DataCon ( splitDataProductType_maybe )
import GHC.Core.Multiplicity ( scaledThing )
import GHC.Utils.Binary
import GHC.Utils.Misc
import GHC.Utils.Outputable
import GHC.Utils.Panic
data Card
= C_00
| C_01
| C_0N
| C_11
| C_1N
| C_10
deriving Card -> Card -> Bool
(Card -> Card -> Bool) -> (Card -> Card -> Bool) -> Eq Card
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Card -> Card -> Bool
$c/= :: Card -> Card -> Bool
== :: Card -> Card -> Bool
$c== :: Card -> Card -> Bool
Eq
_botCard, topCard :: Card
_botCard :: Card
_botCard = Card
C_10
topCard :: Card
topCard = Card
C_0N
isStrict :: Card -> Bool
isStrict :: Card -> Bool
isStrict Card
C_10 = Bool
True
isStrict Card
C_11 = Bool
True
isStrict Card
C_1N = Bool
True
isStrict Card
_ = Bool
False
isAbs :: Card -> Bool
isAbs :: Card -> Bool
isAbs Card
C_00 = Bool
True
isAbs Card
C_10 = Bool
True
isAbs Card
_ = Bool
False
isUsedOnce :: Card -> Bool
isUsedOnce :: Card -> Bool
isUsedOnce Card
C_0N = Bool
False
isUsedOnce Card
C_1N = Bool
False
isUsedOnce Card
_ = Bool
True
oneifyCard :: Card -> Card
oneifyCard :: Card -> Card
oneifyCard Card
C_0N = Card
C_01
oneifyCard Card
C_1N = Card
C_11
oneifyCard Card
c = Card
c
lubCard :: Card -> Card -> Card
lubCard :: Card -> Card -> Card
lubCard Card
C_10 Card
n = Card
n
lubCard Card
n Card
C_10 = Card
n
lubCard Card
C_0N Card
_ = Card
C_0N
lubCard Card
_ Card
C_0N = Card
C_0N
lubCard Card
C_00 Card
C_11 = Card
C_01
lubCard Card
C_11 Card
C_00 = Card
C_01
lubCard Card
C_11 Card
n = Card
n
lubCard Card
n Card
C_11 = Card
n
lubCard Card
C_1N Card
C_1N = Card
C_1N
lubCard Card
_ Card
C_1N = Card
C_0N
lubCard Card
C_1N Card
_ = Card
C_0N
lubCard Card
C_01 Card
_ = Card
C_01
lubCard Card
_ Card
C_01 = Card
C_01
lubCard Card
C_00 Card
C_00 = Card
C_00
plusCard :: Card -> Card -> Card
plusCard :: Card -> Card -> Card
plusCard Card
C_00 Card
n = Card
n
plusCard Card
n Card
C_00 = Card
n
plusCard Card
C_10 Card
C_01 = Card
C_11
plusCard Card
C_10 Card
C_0N = Card
C_1N
plusCard Card
C_10 Card
n = Card
n
plusCard Card
C_01 Card
C_10 = Card
C_11
plusCard Card
C_0N Card
C_10 = Card
C_1N
plusCard Card
n Card
C_10 = Card
n
plusCard Card
C_01 Card
C_01 = Card
C_0N
plusCard Card
C_01 Card
C_0N = Card
C_0N
plusCard Card
C_0N Card
C_01 = Card
C_0N
plusCard Card
C_0N Card
C_0N = Card
C_0N
plusCard Card
_ Card
_ = Card
C_1N
multCard :: Card -> Card -> Card
multCard :: Card -> Card -> Card
multCard Card
C_11 Card
c = Card
c
multCard Card
c Card
C_11 = Card
c
multCard Card
C_00 Card
_ = Card
C_00
multCard Card
_ Card
C_00 = Card
C_00
multCard Card
C_10 Card
c = if Card -> Bool
isStrict Card
c then Card
C_10 else Card
C_00
multCard Card
c Card
C_10 = if Card -> Bool
isStrict Card
c then Card
C_10 else Card
C_00
multCard Card
C_1N Card
C_1N = Card
C_1N
multCard Card
C_01 Card
C_01 = Card
C_01
multCard Card
_ Card
_ = Card
C_0N
data Demand
= !Card :* !SubDemand
deriving Demand -> Demand -> Bool
(Demand -> Demand -> Bool)
-> (Demand -> Demand -> Bool) -> Eq Demand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Demand -> Demand -> Bool
$c/= :: Demand -> Demand -> Bool
== :: Demand -> Demand -> Bool
$c== :: Demand -> Demand -> Bool
Eq
data SubDemand
= Poly !Card
| Call !Card !SubDemand
| Prod ![Demand]
deriving SubDemand -> SubDemand -> Bool
(SubDemand -> SubDemand -> Bool)
-> (SubDemand -> SubDemand -> Bool) -> Eq SubDemand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubDemand -> SubDemand -> Bool
$c/= :: SubDemand -> SubDemand -> Bool
== :: SubDemand -> SubDemand -> Bool
$c== :: SubDemand -> SubDemand -> Bool
Eq
poly00, poly01, poly0N, poly11, poly1N, poly10 :: SubDemand
topSubDmd, botSubDmd, seqSubDmd :: SubDemand
poly00 :: SubDemand
poly00 = Card -> SubDemand
Poly Card
C_00
poly01 :: SubDemand
poly01 = Card -> SubDemand
Poly Card
C_01
poly0N :: SubDemand
poly0N = Card -> SubDemand
Poly Card
C_0N
poly11 :: SubDemand
poly11 = Card -> SubDemand
Poly Card
C_11
poly1N :: SubDemand
poly1N = Card -> SubDemand
Poly Card
C_1N
poly10 :: SubDemand
poly10 = Card -> SubDemand
Poly Card
C_10
topSubDmd :: SubDemand
topSubDmd = SubDemand
poly0N
botSubDmd :: SubDemand
botSubDmd = SubDemand
poly10
seqSubDmd :: SubDemand
seqSubDmd = SubDemand
poly00
polyDmd :: Card -> Demand
polyDmd :: Card -> Demand
polyDmd Card
C_00 = Card
C_00 Card -> SubDemand -> Demand
:* SubDemand
poly00
polyDmd Card
C_01 = Card
C_01 Card -> SubDemand -> Demand
:* SubDemand
poly01
polyDmd Card
C_0N = Card
C_0N Card -> SubDemand -> Demand
:* SubDemand
poly0N
polyDmd Card
C_11 = Card
C_11 Card -> SubDemand -> Demand
:* SubDemand
poly11
polyDmd Card
C_1N = Card
C_1N Card -> SubDemand -> Demand
:* SubDemand
poly1N
polyDmd Card
C_10 = Card
C_10 Card -> SubDemand -> Demand
:* SubDemand
poly10
mkProd :: [Demand] -> SubDemand
mkProd :: [Demand] -> SubDemand
mkProd [] = SubDemand
seqSubDmd
mkProd ds :: [Demand]
ds@(Card
n:*SubDemand
sd : [Demand]
_)
| Card -> Bool
want_to_simplify Card
n, (Demand -> Bool) -> [Demand] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Demand -> Demand -> Bool
forall a. Eq a => a -> a -> Bool
== Card -> Demand
polyDmd Card
n) [Demand]
ds = SubDemand
sd
| Bool
otherwise = [Demand] -> SubDemand
Prod [Demand]
ds
where
want_to_simplify :: Card -> Bool
want_to_simplify Card
C_00 = Bool
True
want_to_simplify Card
C_10 = Bool
True
want_to_simplify Card
_ = Bool
False
viewProd :: Arity -> SubDemand -> Maybe [Demand]
viewProd :: Int -> SubDemand -> Maybe [Demand]
viewProd Int
n (Prod [Demand]
ds) | [Demand]
ds [Demand] -> Int -> Bool
forall a. [a] -> Int -> Bool
`lengthIs` Int
n = [Demand] -> Maybe [Demand]
forall a. a -> Maybe a
Just [Demand]
ds
viewProd Int
n (Poly Card
card) = [Demand] -> Maybe [Demand]
forall a. a -> Maybe a
Just ([Demand] -> Maybe [Demand]) -> [Demand] -> Maybe [Demand]
forall a b. (a -> b) -> a -> b
$! (Int -> Demand -> [Demand]
forall a. Int -> a -> [a]
replicate Int
n (Demand -> [Demand]) -> Demand -> [Demand]
forall a b. (a -> b) -> a -> b
$! Card -> Demand
polyDmd Card
card)
viewProd Int
_ SubDemand
_ = Maybe [Demand]
forall a. Maybe a
Nothing
{-# INLINE viewProd #-}
mkCall :: Card -> SubDemand -> SubDemand
mkCall :: Card -> SubDemand -> SubDemand
mkCall Card
n cd :: SubDemand
cd@(Poly Card
m) | Card
n Card -> Card -> Bool
forall a. Eq a => a -> a -> Bool
== Card
m = SubDemand
cd
mkCall Card
n SubDemand
cd = Card -> SubDemand -> SubDemand
Call Card
n SubDemand
cd
viewCall :: SubDemand -> Maybe (Card, SubDemand)
viewCall :: SubDemand -> Maybe (Card, SubDemand)
viewCall (Call Card
n SubDemand
sd) = (Card, SubDemand) -> Maybe (Card, SubDemand)
forall a. a -> Maybe a
Just (Card
n, SubDemand
sd)
viewCall sd :: SubDemand
sd@(Poly Card
card) = (Card, SubDemand) -> Maybe (Card, SubDemand)
forall a. a -> Maybe a
Just (Card
card, SubDemand
sd)
viewCall SubDemand
_ = Maybe (Card, SubDemand)
forall a. Maybe a
Nothing
topDmd, absDmd, botDmd, seqDmd :: Demand
topDmd :: Demand
topDmd = Card -> Demand
polyDmd Card
C_0N
absDmd :: Demand
absDmd = Card -> Demand
polyDmd Card
C_00
botDmd :: Demand
botDmd = Card -> Demand
polyDmd Card
C_10
seqDmd :: Demand
seqDmd = Card
C_11 Card -> SubDemand -> Demand
:* SubDemand
seqSubDmd
lubSubDmd :: SubDemand -> SubDemand -> SubDemand
lubSubDmd :: SubDemand -> SubDemand -> SubDemand
lubSubDmd (Prod [Demand]
ds1) (Int -> SubDemand -> Maybe [Demand]
viewProd ([Demand] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Demand]
ds1) -> Just [Demand]
ds2) =
[Demand] -> SubDemand
Prod ([Demand] -> SubDemand) -> [Demand] -> SubDemand
forall a b. (a -> b) -> a -> b
$ (Demand -> Demand -> Demand) -> [Demand] -> [Demand] -> [Demand]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
strictZipWith Demand -> Demand -> Demand
lubDmd [Demand]
ds2 [Demand]
ds1
lubSubDmd (Call Card
n1 SubDemand
d1) (SubDemand -> Maybe (Card, SubDemand)
viewCall -> Just (Card
n2, SubDemand
d2))
| Card -> Bool
isAbs Card
n1 = Card -> SubDemand -> SubDemand
mkCall (Card -> Card -> Card
lubCard Card
n1 Card
n2) (SubDemand -> SubDemand -> SubDemand
lubSubDmd SubDemand
botSubDmd SubDemand
d2)
| Card -> Bool
isAbs Card
n2 = Card -> SubDemand -> SubDemand
mkCall (Card -> Card -> Card
lubCard Card
n1 Card
n2) (SubDemand -> SubDemand -> SubDemand
lubSubDmd SubDemand
d1 SubDemand
botSubDmd)
| Bool
otherwise = Card -> SubDemand -> SubDemand
mkCall (Card -> Card -> Card
lubCard Card
n1 Card
n2) (SubDemand -> SubDemand -> SubDemand
lubSubDmd SubDemand
d1 SubDemand
d2)
lubSubDmd (Poly Card
n1) (Poly Card
n2) = Card -> SubDemand
Poly (Card -> Card -> Card
lubCard Card
n1 Card
n2)
lubSubDmd sd1 :: SubDemand
sd1@Poly{} SubDemand
sd2 = SubDemand -> SubDemand -> SubDemand
lubSubDmd SubDemand
sd2 SubDemand
sd1
lubSubDmd SubDemand
_ SubDemand
_ = SubDemand
topSubDmd
lubDmd :: Demand -> Demand -> Demand
lubDmd :: Demand -> Demand -> Demand
lubDmd (Card
n1 :* SubDemand
sd1) (Card
n2 :* SubDemand
sd2) = Card -> Card -> Card
lubCard Card
n1 Card
n2 Card -> SubDemand -> Demand
:* SubDemand -> SubDemand -> SubDemand
lubSubDmd SubDemand
sd1 SubDemand
sd2
plusSubDmd :: SubDemand -> SubDemand -> SubDemand
plusSubDmd :: SubDemand -> SubDemand -> SubDemand
plusSubDmd (Prod [Demand]
ds1) (Int -> SubDemand -> Maybe [Demand]
viewProd ([Demand] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Demand]
ds1) -> Just [Demand]
ds2) =
[Demand] -> SubDemand
Prod ([Demand] -> SubDemand) -> [Demand] -> SubDemand
forall a b. (a -> b) -> a -> b
$ (Demand -> Demand -> Demand) -> [Demand] -> [Demand] -> [Demand]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Demand -> Demand -> Demand
plusDmd [Demand]
ds2 [Demand]
ds1
plusSubDmd (Call Card
n1 SubDemand
d1) (SubDemand -> Maybe (Card, SubDemand)
viewCall -> Just (Card
n2, SubDemand
d2))
| Card -> Bool
isAbs Card
n1 = Card -> SubDemand -> SubDemand
mkCall (Card -> Card -> Card
plusCard Card
n1 Card
n2) (SubDemand -> SubDemand -> SubDemand
lubSubDmd SubDemand
botSubDmd SubDemand
d2)
| Card -> Bool
isAbs Card
n2 = Card -> SubDemand -> SubDemand
mkCall (Card -> Card -> Card
plusCard Card
n1 Card
n2) (SubDemand -> SubDemand -> SubDemand
lubSubDmd SubDemand
d1 SubDemand
botSubDmd)
| Bool
otherwise = Card -> SubDemand -> SubDemand
mkCall (Card -> Card -> Card
plusCard Card
n1 Card
n2) (SubDemand -> SubDemand -> SubDemand
lubSubDmd SubDemand
d1 SubDemand
d2)
plusSubDmd (Poly Card
n1) (Poly Card
n2) = Card -> SubDemand
Poly (Card -> Card -> Card
plusCard Card
n1 Card
n2)
plusSubDmd sd1 :: SubDemand
sd1@Poly{} SubDemand
sd2 = SubDemand -> SubDemand -> SubDemand
plusSubDmd SubDemand
sd2 SubDemand
sd1
plusSubDmd SubDemand
_ SubDemand
_ = SubDemand
topSubDmd
plusDmd :: Demand -> Demand -> Demand
plusDmd :: Demand -> Demand -> Demand
plusDmd (Card
n1 :* SubDemand
sd1) (Card
n2 :* SubDemand
sd2) = Card -> Card -> Card
plusCard Card
n1 Card
n2 Card -> SubDemand -> Demand
:* SubDemand -> SubDemand -> SubDemand
plusSubDmd SubDemand
sd1 SubDemand
sd2
multTrivial :: Card -> a -> a -> Maybe a
multTrivial :: forall a. Card -> a -> a -> Maybe a
multTrivial Card
C_11 a
_ a
a = a -> Maybe a
forall a. a -> Maybe a
Just a
a
multTrivial Card
n a
abs a
_ | Card -> Bool
isAbs Card
n = a -> Maybe a
forall a. a -> Maybe a
Just a
abs
multTrivial Card
_ a
_ a
_ = Maybe a
forall a. Maybe a
Nothing
multSubDmd :: Card -> SubDemand -> SubDemand
multSubDmd :: Card -> SubDemand -> SubDemand
multSubDmd Card
n SubDemand
sd
| Just SubDemand
sd' <- Card -> SubDemand -> SubDemand -> Maybe SubDemand
forall a. Card -> a -> a -> Maybe a
multTrivial Card
n SubDemand
seqSubDmd SubDemand
sd = SubDemand
sd'
multSubDmd Card
n (Poly Card
n') = Card -> SubDemand
Poly (Card -> Card -> Card
multCard Card
n Card
n')
multSubDmd Card
n (Call Card
n' SubDemand
sd) = Card -> SubDemand -> SubDemand
mkCall (Card -> Card -> Card
multCard Card
n Card
n') SubDemand
sd
multSubDmd Card
n (Prod [Demand]
ds) = [Demand] -> SubDemand
Prod ((Demand -> Demand) -> [Demand] -> [Demand]
forall a b. (a -> b) -> [a] -> [b]
map (Card -> Demand -> Demand
multDmd Card
n) [Demand]
ds)
multDmd :: Card -> Demand -> Demand
multDmd :: Card -> Demand -> Demand
multDmd Card
n Demand
dmd
| Just Demand
dmd' <- Card -> Demand -> Demand -> Maybe Demand
forall a. Card -> a -> a -> Maybe a
multTrivial Card
n Demand
absDmd Demand
dmd = Demand
dmd'
multDmd Card
n (Card
m :* SubDemand
dmd) = Card -> Card -> Card
multCard Card
n Card
m Card -> SubDemand -> Demand
:* Card -> SubDemand -> SubDemand
multSubDmd Card
n SubDemand
dmd
isTopDmd :: Demand -> Bool
isTopDmd :: Demand -> Bool
isTopDmd Demand
dmd = Demand
dmd Demand -> Demand -> Bool
forall a. Eq a => a -> a -> Bool
== Demand
topDmd
isAbsDmd :: Demand -> Bool
isAbsDmd :: Demand -> Bool
isAbsDmd (Card
n :* SubDemand
_) = Card -> Bool
isAbs Card
n
isStrictDmd :: Demand -> Bool
isStrictDmd :: Demand -> Bool
isStrictDmd (Card
n :* SubDemand
_) = Card -> Bool
isStrict Card
n
isStrUsedDmd :: Demand -> Bool
isStrUsedDmd :: Demand -> Bool
isStrUsedDmd (Card
n :* SubDemand
_) = Card -> Bool
isStrict Card
n Bool -> Bool -> Bool
&& Bool -> Bool
not (Card -> Bool
isAbs Card
n)
isSeqDmd :: Demand -> Bool
isSeqDmd :: Demand -> Bool
isSeqDmd (Card
C_11 :* SubDemand
sd) = SubDemand
sd SubDemand -> SubDemand -> Bool
forall a. Eq a => a -> a -> Bool
== SubDemand
seqSubDmd
isSeqDmd (Card
C_1N :* SubDemand
sd) = SubDemand
sd SubDemand -> SubDemand -> Bool
forall a. Eq a => a -> a -> Bool
== SubDemand
seqSubDmd
isSeqDmd Demand
_ = Bool
False
isUsedOnceDmd :: Demand -> Bool
isUsedOnceDmd :: Demand -> Bool
isUsedOnceDmd (Card
n :* SubDemand
_) = Card -> Bool
isUsedOnce Card
n
isWeakDmd :: Demand -> Bool
isWeakDmd :: Demand -> Bool
isWeakDmd dmd :: Demand
dmd@(Card
n :* SubDemand
_) = Bool -> Bool
not (Card -> Bool
isStrict Card
n) Bool -> Bool -> Bool
&& Demand -> Bool
is_plus_idem_dmd Demand
dmd
where
is_plus_idem_card :: Card -> Bool
is_plus_idem_card Card
c = Card -> Card -> Card
plusCard Card
c Card
c Card -> Card -> Bool
forall a. Eq a => a -> a -> Bool
== Card
c
is_plus_idem_dmd :: Demand -> Bool
is_plus_idem_dmd (Card
n :* SubDemand
sd) = Card -> Bool
is_plus_idem_card Card
n Bool -> Bool -> Bool
&& SubDemand -> Bool
is_plus_idem_sub_dmd SubDemand
sd
is_plus_idem_sub_dmd :: SubDemand -> Bool
is_plus_idem_sub_dmd (Poly Card
n) = Card -> Bool
is_plus_idem_card Card
n
is_plus_idem_sub_dmd (Prod [Demand]
ds) = (Demand -> Bool) -> [Demand] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Demand -> Bool
is_plus_idem_dmd [Demand]
ds
is_plus_idem_sub_dmd (Call Card
n SubDemand
_) = Card -> Bool
is_plus_idem_card Card
n
evalDmd :: Demand
evalDmd :: Demand
evalDmd = Card
C_1N Card -> SubDemand -> Demand
:* SubDemand
topSubDmd
strictOnceApply1Dmd :: Demand
strictOnceApply1Dmd :: Demand
strictOnceApply1Dmd = Card
C_11 Card -> SubDemand -> Demand
:* Card -> SubDemand -> SubDemand
mkCall Card
C_11 SubDemand
topSubDmd
strictManyApply1Dmd :: Demand
strictManyApply1Dmd :: Demand
strictManyApply1Dmd = Card
C_1N Card -> SubDemand -> Demand
:* Card -> SubDemand -> SubDemand
mkCall Card
C_1N SubDemand
topSubDmd
lazyApply1Dmd :: Demand
lazyApply1Dmd :: Demand
lazyApply1Dmd = Card
C_01 Card -> SubDemand -> Demand
:* Card -> SubDemand -> SubDemand
mkCall Card
C_01 SubDemand
topSubDmd
lazyApply2Dmd :: Demand
lazyApply2Dmd :: Demand
lazyApply2Dmd = Card
C_01 Card -> SubDemand -> Demand
:* Card -> SubDemand -> SubDemand
mkCall Card
C_01 (Card -> SubDemand -> SubDemand
mkCall Card
C_11 SubDemand
topSubDmd)
oneifyDmd :: Demand -> Demand
oneifyDmd :: Demand -> Demand
oneifyDmd (Card
n :* SubDemand
sd) = Card -> Card
oneifyCard Card
n Card -> SubDemand -> Demand
:* SubDemand
sd
strictifyDmd :: Demand -> Demand
strictifyDmd :: Demand -> Demand
strictifyDmd (Card
n :* SubDemand
sd) = Card -> Card -> Card
plusCard Card
C_10 Card
n Card -> SubDemand -> Demand
:* SubDemand
sd
strictifyDictDmd :: Type -> Demand -> Demand
strictifyDictDmd :: Type -> Demand -> Demand
strictifyDictDmd Type
ty (Card
n :* Prod [Demand]
ds)
| Bool -> Bool
not (Card -> Bool
isAbs Card
n)
, Just [Type]
field_tys <- Type -> Maybe [Type]
as_non_newtype_dict Type
ty
= Card
C_1N Card -> SubDemand -> Demand
:*
if (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
isAbsDmd) [Demand]
ds
then SubDemand
topSubDmd
else [Demand] -> SubDemand
Prod ((Type -> Demand -> Demand) -> [Type] -> [Demand] -> [Demand]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Type -> Demand -> Demand
strictifyDictDmd [Type]
field_tys [Demand]
ds)
where
as_non_newtype_dict :: Type -> Maybe [Type]
as_non_newtype_dict Type
ty
| Just (TyCon
tycon, [Type]
_arg_tys, DataCon
_data_con, (Scaled Type -> Type) -> [Scaled Type] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map Scaled Type -> Type
forall a. Scaled a -> a
scaledThing -> [Type]
inst_con_arg_tys)
<- Type -> Maybe (TyCon, [Type], DataCon, [Scaled Type])
splitDataProductType_maybe Type
ty
, Bool -> Bool
not (TyCon -> Bool
isNewTyCon TyCon
tycon)
, TyCon -> Bool
isClassTyCon TyCon
tycon
= [Type] -> Maybe [Type]
forall a. a -> Maybe a
Just [Type]
inst_con_arg_tys
| Bool
otherwise
= Maybe [Type]
forall a. Maybe a
Nothing
strictifyDictDmd Type
_ Demand
dmd = Demand
dmd
mkCalledOnceDmd :: SubDemand -> SubDemand
mkCalledOnceDmd :: SubDemand -> SubDemand
mkCalledOnceDmd SubDemand
sd = Card -> SubDemand -> SubDemand
mkCall Card
C_11 SubDemand
sd
mkCalledOnceDmds :: Arity -> SubDemand -> SubDemand
mkCalledOnceDmds :: Int -> SubDemand -> SubDemand
mkCalledOnceDmds Int
arity SubDemand
sd = (SubDemand -> SubDemand) -> SubDemand -> [SubDemand]
forall a. (a -> a) -> a -> [a]
iterate SubDemand -> SubDemand
mkCalledOnceDmd SubDemand
sd [SubDemand] -> Int -> SubDemand
forall a. [a] -> Int -> a
!! Int
arity
peelCallDmd :: SubDemand -> (Card, SubDemand)
peelCallDmd :: SubDemand -> (Card, SubDemand)
peelCallDmd SubDemand
sd = SubDemand -> Maybe (Card, SubDemand)
viewCall SubDemand
sd Maybe (Card, SubDemand) -> (Card, SubDemand) -> (Card, SubDemand)
forall a. Maybe a -> a -> a
`orElse` (Card
topCard, SubDemand
topSubDmd)
peelManyCalls :: Int -> SubDemand -> Card
peelManyCalls :: Int -> SubDemand -> Card
peelManyCalls Int
0 SubDemand
_ = Card
C_11
peelManyCalls Int
n (SubDemand -> Maybe (Card, SubDemand)
viewCall -> Just (Card
m, SubDemand
sd)) = Card
m Card -> Card -> Card
`multCard` Int -> SubDemand -> Card
peelManyCalls (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) SubDemand
sd
peelManyCalls Int
_ SubDemand
_ = Card
C_0N
mkWorkerDemand :: Int -> Demand
mkWorkerDemand :: Int -> Demand
mkWorkerDemand Int
n = Card
C_01 Card -> SubDemand -> Demand
:* Int -> SubDemand
forall {t}. (Eq t, Num t) => t -> SubDemand
go Int
n
where go :: t -> SubDemand
go t
0 = SubDemand
topSubDmd
go t
n = Card -> SubDemand -> SubDemand
Call Card
C_01 (SubDemand -> SubDemand) -> SubDemand -> SubDemand
forall a b. (a -> b) -> a -> b
$ t -> SubDemand
go (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1)
addCaseBndrDmd :: SubDemand
-> [Demand]
-> [Demand]
addCaseBndrDmd :: SubDemand -> [Demand] -> [Demand]
addCaseBndrDmd (Poly Card
n) [Demand]
alt_dmds
| Card -> Bool
isAbs Card
n = [Demand]
alt_dmds
addCaseBndrDmd SubDemand
sd [Demand]
alt_dmds = (Demand -> Demand -> Demand) -> [Demand] -> [Demand] -> [Demand]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Demand -> Demand -> Demand
plusDmd [Demand]
ds [Demand]
alt_dmds
where
Just [Demand]
ds = Int -> SubDemand -> Maybe [Demand]
viewProd ([Demand] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Demand]
alt_dmds) SubDemand
sd
argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]]
argsOneShots :: StrictSig -> Int -> [[OneShotInfo]]
argsOneShots (StrictSig (DmdType DmdEnv
_ [Demand]
arg_ds Divergence
_)) 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
argOneShots :: Demand
-> [OneShotInfo]
argOneShots :: Demand -> [OneShotInfo]
argOneShots (Card
_ :* SubDemand
sd) = SubDemand -> [OneShotInfo]
go SubDemand
sd
where
go :: SubDemand -> [OneShotInfo]
go (Call Card
n SubDemand
sd)
| Card -> Bool
isUsedOnce Card
n = OneShotInfo
OneShotLam OneShotInfo -> [OneShotInfo] -> [OneShotInfo]
forall a. a -> [a] -> [a]
: SubDemand -> [OneShotInfo]
go SubDemand
sd
| Bool
otherwise = OneShotInfo
NoOneShotInfo OneShotInfo -> [OneShotInfo] -> [OneShotInfo]
forall a. a -> [a] -> [a]
: SubDemand -> [OneShotInfo]
go SubDemand
sd
go SubDemand
_ = []
saturatedByOneShots :: Int -> Demand -> Bool
saturatedByOneShots :: Int -> Demand -> Bool
saturatedByOneShots Int
n (Card
_ :* SubDemand
sd) = Card -> Bool
isUsedOnce (Int -> SubDemand -> Card
peelManyCalls Int
n SubDemand
sd)
data Divergence
= Diverges
| ExnOrDiv
| Dunno
deriving Divergence -> Divergence -> Bool
(Divergence -> Divergence -> Bool)
-> (Divergence -> Divergence -> Bool) -> Eq Divergence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Divergence -> Divergence -> Bool
$c/= :: Divergence -> Divergence -> Bool
== :: Divergence -> Divergence -> Bool
$c== :: Divergence -> Divergence -> Bool
Eq
lubDivergence :: Divergence -> Divergence -> Divergence
lubDivergence :: Divergence -> Divergence -> Divergence
lubDivergence Divergence
Diverges Divergence
div = Divergence
div
lubDivergence Divergence
div Divergence
Diverges = Divergence
div
lubDivergence Divergence
ExnOrDiv Divergence
ExnOrDiv = Divergence
ExnOrDiv
lubDivergence Divergence
_ Divergence
_ = Divergence
Dunno
plusDivergence :: Divergence -> Divergence -> Divergence
plusDivergence :: Divergence -> Divergence -> Divergence
plusDivergence Divergence
Dunno Divergence
Dunno = Divergence
Dunno
plusDivergence Divergence
Diverges Divergence
_ = Divergence
Diverges
plusDivergence Divergence
_ Divergence
Diverges = Divergence
Diverges
plusDivergence Divergence
_ Divergence
_ = Divergence
ExnOrDiv
multDivergence :: Card -> Divergence -> Divergence
multDivergence :: Card -> Divergence -> Divergence
multDivergence Card
n Divergence
_ | Bool -> Bool
not (Card -> Bool
isStrict Card
n) = Divergence
Dunno
multDivergence Card
_ Divergence
d = Divergence
d
topDiv, exnDiv, botDiv :: Divergence
topDiv :: Divergence
topDiv = Divergence
Dunno
exnDiv :: Divergence
exnDiv = Divergence
ExnOrDiv
botDiv :: Divergence
botDiv = Divergence
Diverges
isDeadEndDiv :: Divergence -> Bool
isDeadEndDiv :: Divergence -> Bool
isDeadEndDiv Divergence
Diverges = Bool
True
isDeadEndDiv Divergence
ExnOrDiv = Bool
True
isDeadEndDiv Divergence
Dunno = Bool
False
defaultFvDmd :: Divergence -> Demand
defaultFvDmd :: Divergence -> Demand
defaultFvDmd Divergence
Dunno = Demand
absDmd
defaultFvDmd Divergence
ExnOrDiv = Demand
absDmd
defaultFvDmd Divergence
Diverges = Demand
botDmd
defaultArgDmd :: Divergence -> Demand
defaultArgDmd :: Divergence -> Demand
defaultArgDmd Divergence
Dunno = Demand
topDmd
defaultArgDmd Divergence
ExnOrDiv = Demand
absDmd
defaultArgDmd Divergence
Diverges = Demand
botDmd
type DmdEnv = VarEnv Demand
emptyDmdEnv :: DmdEnv
emptyDmdEnv :: DmdEnv
emptyDmdEnv = DmdEnv
forall a. VarEnv a
emptyVarEnv
multDmdEnv :: Card -> DmdEnv -> DmdEnv
multDmdEnv :: Card -> DmdEnv -> DmdEnv
multDmdEnv Card
n DmdEnv
env
| Just DmdEnv
env' <- Card -> DmdEnv -> DmdEnv -> Maybe DmdEnv
forall a. Card -> a -> a -> Maybe a
multTrivial Card
n DmdEnv
emptyDmdEnv DmdEnv
env = DmdEnv
env'
| Bool
otherwise = (Demand -> Demand) -> DmdEnv -> DmdEnv
forall a b. (a -> b) -> VarEnv a -> VarEnv b
mapVarEnv (Card -> Demand -> Demand
multDmd Card
n) DmdEnv
env
reuseEnv :: DmdEnv -> DmdEnv
reuseEnv :: DmdEnv -> DmdEnv
reuseEnv = Card -> DmdEnv -> DmdEnv
multDmdEnv Card
C_1N
keepAliveDmdEnv :: DmdEnv -> IdSet -> DmdEnv
keepAliveDmdEnv :: DmdEnv -> IdSet -> DmdEnv
keepAliveDmdEnv DmdEnv
env IdSet
vs
= (Var -> DmdEnv -> DmdEnv) -> DmdEnv -> IdSet -> DmdEnv
forall a. (Var -> a -> a) -> a -> IdSet -> a
nonDetStrictFoldVarSet Var -> DmdEnv -> DmdEnv
add DmdEnv
env IdSet
vs
where
add :: Id -> DmdEnv -> DmdEnv
add :: Var -> DmdEnv -> DmdEnv
add Var
v DmdEnv
env = (Demand -> Demand -> Demand) -> DmdEnv -> Var -> Demand -> DmdEnv
forall a. (a -> a -> a) -> VarEnv a -> Var -> a -> VarEnv a
extendVarEnv_C Demand -> Demand -> Demand
add_dmd DmdEnv
env Var
v Demand
topDmd
add_dmd :: Demand -> Demand -> Demand
add_dmd :: Demand -> Demand -> Demand
add_dmd Demand
dmd Demand
_ | Demand -> Bool
isAbsDmd Demand
dmd = Demand
topDmd
| Bool
otherwise = Demand
dmd
data DmdType
= DmdType
{ DmdType -> DmdEnv
dt_env :: !DmdEnv
, DmdType -> [Demand]
dt_args :: ![Demand]
, DmdType -> Divergence
dt_div :: !Divergence
}
instance Eq DmdType where
== :: DmdType -> DmdType -> Bool
(==) (DmdType DmdEnv
fv1 [Demand]
ds1 Divergence
div1)
(DmdType DmdEnv
fv2 [Demand]
ds2 Divergence
div2) = DmdEnv -> [(Unique, Demand)]
forall key elt. UniqFM key elt -> [(Unique, elt)]
nonDetUFMToList DmdEnv
fv1 [(Unique, Demand)] -> [(Unique, Demand)] -> Bool
forall a. Eq a => a -> a -> Bool
== DmdEnv -> [(Unique, Demand)]
forall key elt. UniqFM key 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
&& Divergence
div1 Divergence -> Divergence -> Bool
forall a. Eq a => a -> a -> Bool
== Divergence
div2
lubDmdType :: DmdType -> DmdType -> DmdType
lubDmdType :: DmdType -> DmdType -> DmdType
lubDmdType DmdType
d1 DmdType
d2
= DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType DmdEnv
lub_fv [Demand]
lub_ds Divergence
lub_div
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 Divergence
r1) = Int -> DmdType -> DmdType
etaExpandDmdType Int
n DmdType
d1
(DmdType DmdEnv
fv2 [Demand]
ds2 Divergence
r2) = Int -> DmdType -> DmdType
etaExpandDmdType 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 (Divergence -> Demand
defaultFvDmd Divergence
r1) DmdEnv
fv2 (Divergence -> Demand
defaultFvDmd Divergence
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_div :: Divergence
lub_div = Divergence -> Divergence -> Divergence
lubDivergence Divergence
r1 Divergence
r2
type PlusDmdArg = (DmdEnv, Divergence)
mkPlusDmdArg :: DmdEnv -> PlusDmdArg
mkPlusDmdArg :: DmdEnv -> PlusDmdArg
mkPlusDmdArg DmdEnv
env = (DmdEnv
env, Divergence
topDiv)
toPlusDmdArg :: DmdType -> PlusDmdArg
toPlusDmdArg :: DmdType -> PlusDmdArg
toPlusDmdArg (DmdType DmdEnv
fv [Demand]
_ Divergence
r) = (DmdEnv
fv, Divergence
r)
plusDmdType :: DmdType -> PlusDmdArg -> DmdType
plusDmdType :: DmdType -> PlusDmdArg -> DmdType
plusDmdType (DmdType DmdEnv
fv1 [Demand]
ds1 Divergence
r1) (DmdEnv
fv2, Divergence
t2)
= DmdEnv -> [Demand] -> Divergence -> 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
plusDmd DmdEnv
fv1 (Divergence -> Demand
defaultFvDmd Divergence
r1) DmdEnv
fv2 (Divergence -> Demand
defaultFvDmd Divergence
t2))
[Demand]
ds1
(Divergence
r1 Divergence -> Divergence -> Divergence
`plusDivergence` Divergence
t2)
botDmdType :: DmdType
botDmdType :: DmdType
botDmdType = DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType DmdEnv
emptyDmdEnv [] Divergence
botDiv
nopDmdType :: DmdType
nopDmdType :: DmdType
nopDmdType = DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType DmdEnv
emptyDmdEnv [] Divergence
topDiv
isTopDmdType :: DmdType -> Bool
isTopDmdType :: DmdType -> Bool
isTopDmdType (DmdType DmdEnv
env [Demand]
args Divergence
div)
= Divergence
div Divergence -> Divergence -> Bool
forall a. Eq a => a -> a -> Bool
== Divergence
topDiv Bool -> Bool -> Bool
&& [Demand] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Demand]
args Bool -> Bool -> Bool
&& DmdEnv -> Bool
forall a. VarEnv a -> Bool
isEmptyVarEnv DmdEnv
env
exnDmdType :: DmdType
exnDmdType :: DmdType
exnDmdType = DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType DmdEnv
emptyDmdEnv [] Divergence
exnDiv
dmdTypeDepth :: DmdType -> Arity
dmdTypeDepth :: DmdType -> Int
dmdTypeDepth = [Demand] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Demand] -> Int) -> (DmdType -> [Demand]) -> DmdType -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DmdType -> [Demand]
dt_args
etaExpandDmdType :: Arity -> DmdType -> DmdType
etaExpandDmdType :: Int -> DmdType -> DmdType
etaExpandDmdType Int
n d :: DmdType
d@DmdType{dt_args :: DmdType -> [Demand]
dt_args = [Demand]
ds, dt_div :: DmdType -> Divergence
dt_div = Divergence
div}
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
depth = DmdType
d
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
depth = DmdType
d{dt_args :: [Demand]
dt_args = [Demand]
inc_ds}
| Bool
otherwise = String -> SDoc -> DmdType
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"etaExpandDmdType: arity decrease" (Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
n SDoc -> SDoc -> SDoc
$$ DmdType -> SDoc
forall a. Outputable a => a -> SDoc
ppr DmdType
d)
where depth :: Int
depth = [Demand] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Demand]
ds
inc_ds :: [Demand]
inc_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 (Divergence -> Demand
defaultArgDmd Divergence
div))
decreaseArityDmdType :: DmdType -> DmdType
decreaseArityDmdType :: DmdType -> DmdType
decreaseArityDmdType DmdType
_ = DmdType
nopDmdType
splitDmdTy :: DmdType -> (Demand, DmdType)
splitDmdTy :: DmdType -> (Demand, DmdType)
splitDmdTy ty :: DmdType
ty@DmdType{dt_args :: DmdType -> [Demand]
dt_args=Demand
dmd:[Demand]
args} = (Demand
dmd, DmdType
ty{dt_args :: [Demand]
dt_args=[Demand]
args})
splitDmdTy ty :: DmdType
ty@DmdType{dt_div :: DmdType -> Divergence
dt_div=Divergence
div} = (Divergence -> Demand
defaultArgDmd Divergence
div, DmdType
ty)
multDmdType :: Card -> DmdType -> DmdType
multDmdType :: Card -> DmdType -> DmdType
multDmdType Card
n (DmdType DmdEnv
fv [Demand]
args Divergence
res_ty)
=
DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType (Card -> DmdEnv -> DmdEnv
multDmdEnv Card
n DmdEnv
fv)
((Demand -> Demand) -> [Demand] -> [Demand]
forall a b. (a -> b) -> [a] -> [b]
map (Card -> Demand -> Demand
multDmd Card
n) [Demand]
args)
(Card -> Divergence -> Divergence
multDivergence Card
n Divergence
res_ty)
peelFV :: DmdType -> Var -> (DmdType, Demand)
peelFV :: DmdType -> Var -> (DmdType, Demand)
peelFV (DmdType DmdEnv
fv [Demand]
ds Divergence
res) Var
id =
(DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType DmdEnv
fv' [Demand]
ds Divergence
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` Divergence -> Demand
defaultFvDmd Divergence
res
addDemand :: Demand -> DmdType -> DmdType
addDemand :: Demand -> DmdType -> DmdType
addDemand Demand
dmd (DmdType DmdEnv
fv [Demand]
ds Divergence
res) = DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType DmdEnv
fv (Demand
dmdDemand -> [Demand] -> [Demand]
forall a. a -> [a] -> [a]
:[Demand]
ds) Divergence
res
findIdDemand :: DmdType -> Var -> Demand
findIdDemand :: DmdType -> Var -> Demand
findIdDemand (DmdType DmdEnv
fv [Demand]
_ Divergence
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` Divergence -> Demand
defaultFvDmd Divergence
res
deferAfterPreciseException :: DmdType -> DmdType
deferAfterPreciseException :: DmdType -> DmdType
deferAfterPreciseException = DmdType -> DmdType -> DmdType
lubDmdType DmdType
exnDmdType
keepAliveDmdType :: DmdType -> VarSet -> DmdType
keepAliveDmdType :: DmdType -> IdSet -> DmdType
keepAliveDmdType (DmdType DmdEnv
fvs [Demand]
ds Divergence
res) IdSet
vars =
DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType (DmdEnv
fvs DmdEnv -> IdSet -> DmdEnv
`keepAliveDmdEnv` IdSet
vars) [Demand]
ds Divergence
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
mkStrictSigForArity :: Arity -> DmdType -> StrictSig
mkStrictSigForArity :: Int -> DmdType -> StrictSig
mkStrictSigForArity Int
arity dmd_ty :: DmdType
dmd_ty@(DmdType DmdEnv
fvs [Demand]
args Divergence
div)
| Int
arity Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< DmdType -> Int
dmdTypeDepth DmdType
dmd_ty = DmdType -> StrictSig
StrictSig (DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType DmdEnv
fvs (Int -> [Demand] -> [Demand]
forall a. Int -> [a] -> [a]
take Int
arity [Demand]
args) Divergence
div)
| Bool
otherwise = DmdType -> StrictSig
StrictSig (Int -> DmdType -> DmdType
etaExpandDmdType Int
arity DmdType
dmd_ty)
mkClosedStrictSig :: [Demand] -> Divergence -> StrictSig
mkClosedStrictSig :: [Demand] -> Divergence -> StrictSig
mkClosedStrictSig [Demand]
ds Divergence
res = Int -> DmdType -> StrictSig
mkStrictSigForArity ([Demand] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Demand]
ds) (DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType DmdEnv
emptyDmdEnv [Demand]
ds Divergence
res)
splitStrictSig :: StrictSig -> ([Demand], Divergence)
splitStrictSig :: StrictSig -> ([Demand], Divergence)
splitStrictSig (StrictSig (DmdType DmdEnv
_ [Demand]
dmds Divergence
res)) = ([Demand]
dmds, Divergence
res)
strictSigDmdEnv :: StrictSig -> DmdEnv
strictSigDmdEnv :: StrictSig -> DmdEnv
strictSigDmdEnv (StrictSig (DmdType DmdEnv
env [Demand]
_ Divergence
_)) = DmdEnv
env
hasDemandEnvSig :: StrictSig -> Bool
hasDemandEnvSig :: StrictSig -> Bool
hasDemandEnvSig = Bool -> Bool
not (Bool -> Bool) -> (StrictSig -> Bool) -> StrictSig -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DmdEnv -> Bool
forall a. VarEnv a -> Bool
isEmptyVarEnv (DmdEnv -> Bool) -> (StrictSig -> DmdEnv) -> StrictSig -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSig -> DmdEnv
strictSigDmdEnv
botSig :: StrictSig
botSig :: StrictSig
botSig = DmdType -> StrictSig
StrictSig DmdType
botDmdType
nopSig :: StrictSig
nopSig :: StrictSig
nopSig = DmdType -> StrictSig
StrictSig DmdType
nopDmdType
isTopSig :: StrictSig -> Bool
isTopSig :: StrictSig -> Bool
isTopSig (StrictSig DmdType
ty) = DmdType -> Bool
isTopDmdType DmdType
ty
isDeadEndSig :: StrictSig -> Bool
isDeadEndSig :: StrictSig -> Bool
isDeadEndSig (StrictSig (DmdType DmdEnv
_ [Demand]
_ Divergence
res)) = Divergence -> Bool
isDeadEndDiv Divergence
res
appIsDeadEnd :: StrictSig -> Int -> Bool
appIsDeadEnd :: StrictSig -> Int -> Bool
appIsDeadEnd (StrictSig (DmdType DmdEnv
_ [Demand]
ds Divergence
res)) Int
n
= Divergence -> Bool
isDeadEndDiv Divergence
res Bool -> Bool -> Bool
&& Bool -> Bool
not ([Demand] -> Int -> Bool
forall a. [a] -> Int -> Bool
lengthExceeds [Demand]
ds Int
n)
prependArgsStrictSig :: Int -> StrictSig -> StrictSig
prependArgsStrictSig :: Int -> StrictSig -> StrictSig
prependArgsStrictSig Int
new_args sig :: StrictSig
sig@(StrictSig dmd_ty :: DmdType
dmd_ty@(DmdType DmdEnv
env [Demand]
dmds Divergence
res))
| Int
new_args Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = StrictSig
sig
| DmdType -> Bool
isTopDmdType DmdType
dmd_ty = StrictSig
sig
| Int
new_args Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = String -> SDoc -> StrictSig
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"prependArgsStrictSig: negative new_args"
(Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
new_args SDoc -> SDoc -> SDoc
$$ StrictSig -> SDoc
forall a. Outputable a => a -> SDoc
ppr StrictSig
sig)
| Bool
otherwise = DmdType -> StrictSig
StrictSig (DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType DmdEnv
env [Demand]
dmds' Divergence
res)
where
dmds' :: [Demand]
dmds' = Int -> Demand -> [Demand]
forall a. Int -> a -> [a]
replicate Int
new_args Demand
topDmd [Demand] -> [Demand] -> [Demand]
forall a. [a] -> [a] -> [a]
++ [Demand]
dmds
etaConvertStrictSig :: Arity -> StrictSig -> StrictSig
etaConvertStrictSig :: Int -> StrictSig -> StrictSig
etaConvertStrictSig Int
arity (StrictSig DmdType
dmd_ty)
| Int
arity Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< DmdType -> Int
dmdTypeDepth DmdType
dmd_ty = DmdType -> StrictSig
StrictSig (DmdType -> StrictSig) -> DmdType -> StrictSig
forall a b. (a -> b) -> a -> b
$ DmdType -> DmdType
decreaseArityDmdType DmdType
dmd_ty
| Bool
otherwise = DmdType -> StrictSig
StrictSig (DmdType -> StrictSig) -> DmdType -> StrictSig
forall a b. (a -> b) -> a -> b
$ Int -> DmdType -> DmdType
etaExpandDmdType Int
arity DmdType
dmd_ty
type DmdTransformer = SubDemand -> DmdType
dmdTransformSig :: StrictSig -> DmdTransformer
dmdTransformSig :: StrictSig -> DmdTransformer
dmdTransformSig (StrictSig dmd_ty :: DmdType
dmd_ty@(DmdType DmdEnv
_ [Demand]
arg_ds Divergence
_)) SubDemand
sd
= Card -> DmdType -> DmdType
multDmdType (Int -> SubDemand -> Card
peelManyCalls ([Demand] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Demand]
arg_ds) SubDemand
sd) DmdType
dmd_ty
dmdTransformDataConSig :: Arity -> DmdTransformer
dmdTransformDataConSig :: Int -> DmdTransformer
dmdTransformDataConSig Int
arity SubDemand
sd = case Int -> SubDemand -> Maybe [Demand]
go Int
arity SubDemand
sd of
Just [Demand]
dmds -> DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType DmdEnv
emptyDmdEnv [Demand]
dmds Divergence
topDiv
Maybe [Demand]
Nothing -> DmdType
nopDmdType
where
go :: Int -> SubDemand -> Maybe [Demand]
go Int
0 SubDemand
sd = Int -> SubDemand -> Maybe [Demand]
viewProd Int
arity SubDemand
sd
go Int
n (SubDemand -> Maybe (Card, SubDemand)
viewCall -> Just (Card
C_11, SubDemand
sd)) = Int -> SubDemand -> Maybe [Demand]
go (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) SubDemand
sd
go Int
_ SubDemand
_ = Maybe [Demand]
forall a. Maybe a
Nothing
dmdTransformDictSelSig :: StrictSig -> DmdTransformer
dmdTransformDictSelSig :: StrictSig -> DmdTransformer
dmdTransformDictSelSig (StrictSig (DmdType DmdEnv
_ [(Card
_ :* SubDemand
sig_sd)] Divergence
_)) SubDemand
call_sd
| (Card
n, SubDemand
sd') <- SubDemand -> (Card, SubDemand)
peelCallDmd SubDemand
call_sd
, Prod [Demand]
sig_ds <- SubDemand
sig_sd
= Card -> DmdType -> DmdType
multDmdType Card
n (DmdType -> DmdType) -> DmdType -> DmdType
forall a b. (a -> b) -> a -> b
$
DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType DmdEnv
emptyDmdEnv [Card
C_11 Card -> SubDemand -> Demand
:* [Demand] -> SubDemand
Prod ((Demand -> Demand) -> [Demand] -> [Demand]
forall a b. (a -> b) -> [a] -> [b]
map (SubDemand -> Demand -> Demand
enhance SubDemand
sd') [Demand]
sig_ds)] Divergence
topDiv
| Bool
otherwise
= DmdType
nopDmdType
where
enhance :: SubDemand -> Demand -> Demand
enhance SubDemand
sd Demand
old | Demand -> Bool
isAbsDmd Demand
old = Demand
old
| Bool
otherwise = Card
C_11 Card -> SubDemand -> Demand
:* SubDemand
sd
dmdTransformDictSelSig StrictSig
sig SubDemand
sd = String -> SDoc -> DmdType
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"dmdTransformDictSelSig: no args" (StrictSig -> SDoc
forall a. Outputable a => a -> SDoc
ppr StrictSig
sig SDoc -> SDoc -> SDoc
$$ SubDemand -> SDoc
forall a. Outputable a => a -> SDoc
ppr SubDemand
sd)
zapDmdEnvSig :: StrictSig -> StrictSig
zapDmdEnvSig :: StrictSig -> StrictSig
zapDmdEnvSig (StrictSig (DmdType DmdEnv
_ [Demand]
ds Divergence
r)) = [Demand] -> Divergence -> StrictSig
mkClosedStrictSig [Demand]
ds Divergence
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
{ 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
{ 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 Divergence
r))
= DmdType -> StrictSig
StrictSig (DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType DmdEnv
env ((Demand -> Demand) -> [Demand] -> [Demand]
forall a b. (a -> b) -> [a] -> [b]
map Demand -> Demand
zapUsedOnceDemand [Demand]
ds) Divergence
r)
data KillFlags = KillFlags
{ KillFlags -> Bool
kf_abs :: Bool
, KillFlags -> Bool
kf_used_once :: Bool
, KillFlags -> Bool
kf_called_once :: Bool
}
kill_usage_card :: KillFlags -> Card -> Card
kill_usage_card :: KillFlags -> Card -> Card
kill_usage_card KillFlags
kfs Card
C_00 | KillFlags -> Bool
kf_abs KillFlags
kfs = Card
C_0N
kill_usage_card KillFlags
kfs Card
C_10 | KillFlags -> Bool
kf_abs KillFlags
kfs = Card
C_1N
kill_usage_card KillFlags
kfs Card
C_01 | KillFlags -> Bool
kf_used_once KillFlags
kfs = Card
C_0N
kill_usage_card KillFlags
kfs Card
C_11 | KillFlags -> Bool
kf_used_once KillFlags
kfs = Card
C_1N
kill_usage_card KillFlags
_ Card
n = Card
n
kill_usage :: KillFlags -> Demand -> Demand
kill_usage :: KillFlags -> Demand -> Demand
kill_usage KillFlags
kfs (Card
n :* SubDemand
sd) = KillFlags -> Card -> Card
kill_usage_card KillFlags
kfs Card
n Card -> SubDemand -> Demand
:* KillFlags -> SubDemand -> SubDemand
kill_usage_sd KillFlags
kfs SubDemand
sd
kill_usage_sd :: KillFlags -> SubDemand -> SubDemand
kill_usage_sd :: KillFlags -> SubDemand -> SubDemand
kill_usage_sd KillFlags
kfs (Call Card
n SubDemand
sd)
| KillFlags -> Bool
kf_called_once KillFlags
kfs = Card -> SubDemand -> SubDemand
mkCall (Card -> Card -> Card
lubCard Card
C_1N Card
n) (KillFlags -> SubDemand -> SubDemand
kill_usage_sd KillFlags
kfs SubDemand
sd)
| Bool
otherwise = Card -> SubDemand -> SubDemand
mkCall Card
n (KillFlags -> SubDemand -> SubDemand
kill_usage_sd KillFlags
kfs SubDemand
sd)
kill_usage_sd KillFlags
kfs (Prod [Demand]
ds) = [Demand] -> SubDemand
Prod ((Demand -> Demand) -> [Demand] -> [Demand]
forall a b. (a -> b) -> [a] -> [b]
map (KillFlags -> Demand -> Demand
kill_usage KillFlags
kfs) [Demand]
ds)
kill_usage_sd KillFlags
_ SubDemand
sd = SubDemand
sd
data TypeShape
= TsFun TypeShape
| TsProd [TypeShape]
| TsUnk
trimToType :: Demand -> TypeShape -> Demand
trimToType :: Demand -> TypeShape -> Demand
trimToType (Card
n :* SubDemand
sd) TypeShape
ts
= Card
n Card -> SubDemand -> Demand
:* SubDemand -> TypeShape -> SubDemand
go SubDemand
sd TypeShape
ts
where
go :: SubDemand -> TypeShape -> SubDemand
go (Prod [Demand]
ds) (TsProd [TypeShape]
tss)
| [Demand] -> [TypeShape] -> Bool
forall a b. [a] -> [b] -> Bool
equalLength [Demand]
ds [TypeShape]
tss = [Demand] -> SubDemand
Prod ((Demand -> TypeShape -> Demand)
-> [Demand] -> [TypeShape] -> [Demand]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Demand -> TypeShape -> Demand
trimToType [Demand]
ds [TypeShape]
tss)
go (Call Card
n SubDemand
sd) (TsFun TypeShape
ts) = Card -> SubDemand -> SubDemand
mkCall Card
n (SubDemand -> TypeShape -> SubDemand
go SubDemand
sd TypeShape
ts)
go sd :: SubDemand
sd@Poly{} TypeShape
_ = SubDemand
sd
go SubDemand
_ TypeShape
_ = SubDemand
topSubDmd
seqDemand :: Demand -> ()
seqDemand :: Demand -> ()
seqDemand (Card
_ :* SubDemand
sd) = SubDemand -> ()
seqSubDemand SubDemand
sd
seqSubDemand :: SubDemand -> ()
seqSubDemand :: SubDemand -> ()
seqSubDemand (Prod [Demand]
ds) = [Demand] -> ()
seqDemandList [Demand]
ds
seqSubDemand (Call Card
_ SubDemand
sd) = SubDemand -> ()
seqSubDemand SubDemand
sd
seqSubDemand (Poly Card
_) = ()
seqDemandList :: [Demand] -> ()
seqDemandList :: [Demand] -> ()
seqDemandList = (Demand -> () -> ()) -> () -> [Demand] -> ()
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (() -> () -> ()
seq (() -> () -> ()) -> (Demand -> ()) -> Demand -> () -> ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Demand -> ()
seqDemand) ()
seqDmdType :: DmdType -> ()
seqDmdType :: DmdType -> ()
seqDmdType (DmdType DmdEnv
env [Demand]
ds Divergence
res) =
DmdEnv -> ()
seqDmdEnv DmdEnv
env () -> () -> ()
`seq` [Demand] -> ()
seqDemandList [Demand]
ds () -> () -> ()
`seq` Divergence
res Divergence -> () -> ()
`seq` ()
seqDmdEnv :: DmdEnv -> ()
seqDmdEnv :: DmdEnv -> ()
seqDmdEnv DmdEnv
env = ([Demand] -> ()) -> DmdEnv -> ()
forall elt key. ([elt] -> ()) -> UniqFM key elt -> ()
seqEltsUFM [Demand] -> ()
seqDemandList DmdEnv
env
seqStrictSig :: StrictSig -> ()
seqStrictSig :: StrictSig -> ()
seqStrictSig (StrictSig DmdType
ty) = DmdType -> ()
seqDmdType DmdType
ty
instance Outputable Card where
ppr :: Card -> SDoc
ppr Card
C_00 = Char -> SDoc
char Char
'A'
ppr Card
C_01 = Char -> SDoc
char Char
'M'
ppr Card
C_0N = Char -> SDoc
char Char
'L'
ppr Card
C_11 = Char -> SDoc
char Char
'1'
ppr Card
C_1N = Char -> SDoc
char Char
'S'
ppr Card
C_10 = Char -> SDoc
char Char
'B'
instance Outputable Demand where
ppr :: Demand -> SDoc
ppr dmd :: Demand
dmd@(Card
n :* SubDemand
sd)
| Card -> Bool
isAbs Card
n = Card -> SDoc
forall a. Outputable a => a -> SDoc
ppr Card
n
| Demand
dmd Demand -> Demand -> Bool
forall a. Eq a => a -> a -> Bool
== Card -> Demand
polyDmd Card
n = Card -> SDoc
forall a. Outputable a => a -> SDoc
ppr Card
n
| Bool
otherwise = Card -> SDoc
forall a. Outputable a => a -> SDoc
ppr Card
n SDoc -> SDoc -> SDoc
<> SubDemand -> SDoc
forall a. Outputable a => a -> SDoc
ppr SubDemand
sd
instance Outputable SubDemand where
ppr :: SubDemand -> SDoc
ppr (Poly Card
sd) = Card -> SDoc
forall a. Outputable a => a -> SDoc
ppr Card
sd
ppr (Call Card
n SubDemand
sd) = Char -> SDoc
char Char
'C' SDoc -> SDoc -> SDoc
<> Card -> SDoc
forall a. Outputable a => a -> SDoc
ppr Card
n SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
parens (SubDemand -> SDoc
forall a. Outputable a => a -> SDoc
ppr SubDemand
sd)
ppr (Prod [Demand]
ds) = Char -> SDoc
char Char
'P' SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
parens ([Demand] -> SDoc
forall {a}. Outputable a => [a] -> SDoc
fields [Demand]
ds)
where
fields :: [a] -> SDoc
fields [] = SDoc
empty
fields [a
x] = a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
x
fields (a
x:[a]
xs) = a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
x SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
',' SDoc -> SDoc -> SDoc
<> [a] -> SDoc
fields [a]
xs
instance Outputable Divergence where
ppr :: Divergence -> SDoc
ppr Divergence
Diverges = Char -> SDoc
char Char
'b'
ppr Divergence
ExnOrDiv = Char -> SDoc
char Char
'x'
ppr Divergence
Dunno = SDoc
empty
instance Outputable DmdType where
ppr :: DmdType -> SDoc
ppr (DmdType DmdEnv
fv [Demand]
ds Divergence
res)
= [SDoc] -> SDoc
hsep [[SDoc] -> SDoc
hcat ((Demand -> SDoc) -> [Demand] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (SDoc -> SDoc
angleBrackets (SDoc -> SDoc) -> (Demand -> SDoc) -> Demand -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Demand -> SDoc
forall a. Outputable a => a -> SDoc
ppr) [Demand]
ds) SDoc -> SDoc -> SDoc
<> Divergence -> SDoc
forall a. Outputable a => a -> SDoc
ppr Divergence
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 key elt. UniqFM key elt -> [(Unique, elt)]
nonDetUFMToList DmdEnv
fv
instance Outputable StrictSig where
ppr :: StrictSig -> SDoc
ppr (StrictSig DmdType
ty) = DmdType -> SDoc
forall a. Outputable a => a -> SDoc
ppr DmdType
ty
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)
instance Binary Card where
put_ :: BinHandle -> Card -> IO ()
put_ BinHandle
bh Card
C_00 = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh Card
C_01 = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
put_ BinHandle
bh Card
C_0N = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
put_ BinHandle
bh Card
C_11 = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
put_ BinHandle
bh Card
C_1N = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4
put_ BinHandle
bh Card
C_10 = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
5
get :: BinHandle -> IO Card
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> Card -> IO Card
forall (m :: * -> *) a. Monad m => a -> m a
return Card
C_00
Word8
1 -> Card -> IO Card
forall (m :: * -> *) a. Monad m => a -> m a
return Card
C_01
Word8
2 -> Card -> IO Card
forall (m :: * -> *) a. Monad m => a -> m a
return Card
C_0N
Word8
3 -> Card -> IO Card
forall (m :: * -> *) a. Monad m => a -> m a
return Card
C_11
Word8
4 -> Card -> IO Card
forall (m :: * -> *) a. Monad m => a -> m a
return Card
C_1N
Word8
5 -> Card -> IO Card
forall (m :: * -> *) a. Monad m => a -> m a
return Card
C_10
Word8
_ -> String -> SDoc -> IO Card
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Binary:Card" (Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
h :: Int))
instance Binary Demand where
put_ :: BinHandle -> Demand -> IO ()
put_ BinHandle
bh (Card
n :* SubDemand
sd) = BinHandle -> Card -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Card
n IO () -> IO () -> IO ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> BinHandle -> SubDemand -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SubDemand
sd
get :: BinHandle -> IO Demand
get BinHandle
bh = Card -> SubDemand -> Demand
(:*) (Card -> SubDemand -> Demand)
-> IO Card -> IO (SubDemand -> Demand)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Card
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (SubDemand -> Demand) -> IO SubDemand -> IO Demand
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO SubDemand
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
instance Binary SubDemand where
put_ :: BinHandle -> SubDemand -> IO ()
put_ BinHandle
bh (Poly Card
sd) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0 IO () -> IO () -> IO ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> BinHandle -> Card -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Card
sd
put_ BinHandle
bh (Call Card
n SubDemand
sd) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1 IO () -> IO () -> IO ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> BinHandle -> Card -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Card
n IO () -> IO () -> IO ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> BinHandle -> SubDemand -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SubDemand
sd
put_ BinHandle
bh (Prod [Demand]
ds) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2 IO () -> IO () -> IO ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> BinHandle -> [Demand] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Demand]
ds
get :: BinHandle -> IO SubDemand
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> Card -> SubDemand
Poly (Card -> SubDemand) -> IO Card -> IO SubDemand
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Card
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
1 -> Card -> SubDemand -> SubDemand
mkCall (Card -> SubDemand -> SubDemand)
-> IO Card -> IO (SubDemand -> SubDemand)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Card
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (SubDemand -> SubDemand) -> IO SubDemand -> IO SubDemand
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO SubDemand
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
2 -> [Demand] -> SubDemand
Prod ([Demand] -> SubDemand) -> IO [Demand] -> IO SubDemand
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO [Demand]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
_ -> String -> SDoc -> IO SubDemand
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Binary:SubDemand" (Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
h :: Int))
instance Binary StrictSig where
put_ :: BinHandle -> StrictSig -> IO ()
put_ BinHandle
bh (StrictSig DmdType
aa) = BinHandle -> DmdType -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh DmdType
aa
get :: BinHandle -> IO StrictSig
get BinHandle
bh = DmdType -> StrictSig
StrictSig (DmdType -> StrictSig) -> IO DmdType -> IO StrictSig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO DmdType
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
instance Binary DmdType where
put_ :: BinHandle -> DmdType -> IO ()
put_ BinHandle
bh (DmdType DmdEnv
_ [Demand]
ds Divergence
dr) = BinHandle -> [Demand] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Demand]
ds IO () -> IO () -> IO ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> BinHandle -> Divergence -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Divergence
dr
get :: BinHandle -> IO DmdType
get BinHandle
bh = DmdEnv -> [Demand] -> Divergence -> DmdType
DmdType DmdEnv
emptyDmdEnv ([Demand] -> Divergence -> DmdType)
-> IO [Demand] -> IO (Divergence -> DmdType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO [Demand]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (Divergence -> DmdType) -> IO Divergence -> IO DmdType
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO Divergence
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
instance Binary Divergence where
put_ :: BinHandle -> Divergence -> IO ()
put_ BinHandle
bh Divergence
Dunno = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh Divergence
ExnOrDiv = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
put_ BinHandle
bh Divergence
Diverges = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
get :: BinHandle -> IO Divergence
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> Divergence -> IO Divergence
forall (m :: * -> *) a. Monad m => a -> m a
return Divergence
Dunno
Word8
1 -> Divergence -> IO Divergence
forall (m :: * -> *) a. Monad m => a -> m a
return Divergence
ExnOrDiv
Word8
2 -> Divergence -> IO Divergence
forall (m :: * -> *) a. Monad m => a -> m a
return Divergence
Diverges
Word8
_ -> String -> SDoc -> IO Divergence
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Binary:Divergence" (Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
h :: Int))