{-# LANGUAGE DerivingVia #-}
{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
module GHC.Core.Opt.Stats (
SimplCount, doSimplTick, doFreeSimplTick, simplCountN,
pprSimplCount, plusSimplCount, zeroSimplCount,
isZeroSimplCount, hasDetailedCounts, Tick(..)
) where
import GHC.Prelude
import GHC.Types.Var
import GHC.Types.Error
import GHC.Utils.Outputable as Outputable
import GHC.Data.FastString
import Data.List (sortOn)
import Data.List.NonEmpty (NonEmpty(..))
import qualified Data.List.NonEmpty as NE
import Data.Ord
import Data.Map (Map)
import qualified Data.Map as Map
import qualified Data.Map.Strict as MapStrict
import GHC.Utils.Panic (throwGhcException, GhcException(..))
getVerboseSimplStats :: (Bool -> SDoc) -> SDoc
getVerboseSimplStats :: (Bool -> SDoc) -> SDoc
getVerboseSimplStats = forall doc. IsOutput doc => (Bool -> doc) -> doc
getPprDebug
zeroSimplCount :: Bool
-> SimplCount
isZeroSimplCount :: SimplCount -> Bool
hasDetailedCounts :: SimplCount -> Bool
pprSimplCount :: SimplCount -> SDoc
doSimplTick :: Int
-> Tick -> SimplCount -> SimplCount
doFreeSimplTick :: Tick -> SimplCount -> SimplCount
plusSimplCount :: SimplCount -> SimplCount -> SimplCount
data SimplCount
= VerySimplCount !Int
| SimplCount {
SimplCount -> Int
ticks :: !Int,
SimplCount -> TickCounts
details :: !TickCounts,
SimplCount -> Int
n_log :: !Int,
SimplCount -> [Tick]
log1 :: [Tick],
SimplCount -> [Tick]
log2 :: [Tick]
}
type TickCounts = Map Tick Int
simplCountN :: SimplCount -> Int
simplCountN :: SimplCount -> Int
simplCountN (VerySimplCount Int
n) = Int
n
simplCountN (SimplCount { ticks :: SimplCount -> Int
ticks = Int
n }) = Int
n
zeroSimplCount :: Bool -> SimplCount
zeroSimplCount Bool
dump_simpl_stats
| Bool
dump_simpl_stats
= SimplCount {ticks :: Int
ticks = Int
0, details :: TickCounts
details = forall k a. Map k a
Map.empty,
n_log :: Int
n_log = Int
0, log1 :: [Tick]
log1 = [], log2 :: [Tick]
log2 = []}
| Bool
otherwise
= Int -> SimplCount
VerySimplCount Int
0
isZeroSimplCount :: SimplCount -> Bool
isZeroSimplCount (VerySimplCount Int
n) = Int
nforall a. Eq a => a -> a -> Bool
==Int
0
isZeroSimplCount (SimplCount { ticks :: SimplCount -> Int
ticks = Int
n }) = Int
nforall a. Eq a => a -> a -> Bool
==Int
0
hasDetailedCounts :: SimplCount -> Bool
hasDetailedCounts (VerySimplCount {}) = Bool
False
hasDetailedCounts (SimplCount {}) = Bool
True
doFreeSimplTick :: Tick -> SimplCount -> SimplCount
doFreeSimplTick Tick
tick sc :: SimplCount
sc@SimplCount { details :: SimplCount -> TickCounts
details = TickCounts
dts }
= SimplCount
sc { details :: TickCounts
details = TickCounts
dts TickCounts -> Tick -> TickCounts
`addTick` Tick
tick }
doFreeSimplTick Tick
_ SimplCount
sc = SimplCount
sc
doSimplTick :: Int -> Tick -> SimplCount -> SimplCount
doSimplTick Int
history_size Tick
tick
sc :: SimplCount
sc@(SimplCount { ticks :: SimplCount -> Int
ticks = Int
tks, details :: SimplCount -> TickCounts
details = TickCounts
dts, n_log :: SimplCount -> Int
n_log = Int
nl, log1 :: SimplCount -> [Tick]
log1 = [Tick]
l1 })
| Int
nl forall a. Ord a => a -> a -> Bool
>= Int
history_size = SimplCount
sc1 { n_log :: Int
n_log = Int
1, log1 :: [Tick]
log1 = [Tick
tick], log2 :: [Tick]
log2 = [Tick]
l1 }
| Bool
otherwise = SimplCount
sc1 { n_log :: Int
n_log = Int
nlforall a. Num a => a -> a -> a
+Int
1, log1 :: [Tick]
log1 = Tick
tick forall a. a -> [a] -> [a]
: [Tick]
l1 }
where
sc1 :: SimplCount
sc1 = SimplCount
sc { ticks :: Int
ticks = Int
tksforall a. Num a => a -> a -> a
+Int
1, details :: TickCounts
details = TickCounts
dts TickCounts -> Tick -> TickCounts
`addTick` Tick
tick }
doSimplTick Int
_ Tick
_ (VerySimplCount Int
n) = Int -> SimplCount
VerySimplCount (Int
nforall a. Num a => a -> a -> a
+Int
1)
addTick :: TickCounts -> Tick -> TickCounts
addTick :: TickCounts -> Tick -> TickCounts
addTick TickCounts
fm Tick
tick = forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
MapStrict.insertWith forall a. Num a => a -> a -> a
(+) Tick
tick Int
1 TickCounts
fm
plusSimplCount :: SimplCount -> SimplCount -> SimplCount
plusSimplCount sc1 :: SimplCount
sc1@(SimplCount { ticks :: SimplCount -> Int
ticks = Int
tks1, details :: SimplCount -> TickCounts
details = TickCounts
dts1 })
sc2 :: SimplCount
sc2@(SimplCount { ticks :: SimplCount -> Int
ticks = Int
tks2, details :: SimplCount -> TickCounts
details = TickCounts
dts2 })
= SimplCount
log_base { ticks :: Int
ticks = Int
tks1 forall a. Num a => a -> a -> a
+ Int
tks2
, details :: TickCounts
details = forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
MapStrict.unionWith forall a. Num a => a -> a -> a
(+) TickCounts
dts1 TickCounts
dts2 }
where
log_base :: SimplCount
log_base | forall (t :: * -> *) a. Foldable t => t a -> Bool
null (SimplCount -> [Tick]
log1 SimplCount
sc2) = SimplCount
sc1
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null (SimplCount -> [Tick]
log2 SimplCount
sc2) = SimplCount
sc2 { log2 :: [Tick]
log2 = SimplCount -> [Tick]
log1 SimplCount
sc1 }
| Bool
otherwise = SimplCount
sc2
plusSimplCount (VerySimplCount Int
n) (VerySimplCount Int
m) = Int -> SimplCount
VerySimplCount (Int
nforall a. Num a => a -> a -> a
+Int
m)
plusSimplCount SimplCount
lhs SimplCount
rhs =
forall a. GhcException -> a
throwGhcException forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> SDoc -> GhcException
PprProgramError String
"plusSimplCount" forall a b. (a -> b) -> a -> b
$ forall doc. IsDoc doc => [doc] -> doc
vcat
[ forall doc. IsLine doc => String -> doc
text String
"lhs"
, SimplCount -> SDoc
pprSimplCount SimplCount
lhs
, forall doc. IsLine doc => String -> doc
text String
"rhs"
, SimplCount -> SDoc
pprSimplCount SimplCount
rhs
]
pprSimplCount :: SimplCount -> SDoc
pprSimplCount (VerySimplCount Int
n) = forall doc. IsLine doc => String -> doc
text String
"Total ticks:" forall doc. IsLine doc => doc -> doc -> doc
<+> forall doc. IsLine doc => Int -> doc
int Int
n
pprSimplCount (SimplCount { ticks :: SimplCount -> Int
ticks = Int
tks, details :: SimplCount -> TickCounts
details = TickCounts
dts, log1 :: SimplCount -> [Tick]
log1 = [Tick]
l1, log2 :: SimplCount -> [Tick]
log2 = [Tick]
l2 })
= forall doc. IsDoc doc => [doc] -> doc
vcat [forall doc. IsLine doc => String -> doc
text String
"Total ticks: " forall doc. IsLine doc => doc -> doc -> doc
<+> forall doc. IsLine doc => Int -> doc
int Int
tks,
SDoc
blankLine,
TickCounts -> SDoc
pprTickCounts TickCounts
dts,
(Bool -> SDoc) -> SDoc
getVerboseSimplStats forall a b. (a -> b) -> a -> b
$ \Bool
dbg -> if Bool
dbg
then
forall doc. IsDoc doc => [doc] -> doc
vcat [SDoc
blankLine,
forall doc. IsLine doc => String -> doc
text String
"Log (most recent first)",
Int -> SDoc -> SDoc
nest Int
4 (forall doc. IsDoc doc => [doc] -> doc
vcat (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [Tick]
l1) forall doc. IsDoc doc => doc -> doc -> doc
$$ forall doc. IsDoc doc => [doc] -> doc
vcat (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [Tick]
l2))]
else forall doc. IsOutput doc => doc
Outputable.empty
]
pprTickCounts :: Map Tick Int -> SDoc
pprTickCounts :: TickCounts -> SDoc
pprTickCounts TickCounts
counts
= forall doc. IsDoc doc => [doc] -> doc
vcat (forall a b. (a -> b) -> [a] -> [b]
map NonEmpty (Tick, Int) -> SDoc
pprTickGroup [NonEmpty (Tick, Int)]
groups)
where
groups :: [NonEmpty (Tick, Int)]
groups :: [NonEmpty (Tick, Int)]
groups = forall (f :: * -> *) b a.
(Foldable f, Eq b) =>
(a -> b) -> f a -> [NonEmpty a]
NE.groupWith (Tick -> Int
tickToTag forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) (forall k a. Map k a -> [(k, a)]
Map.toList TickCounts
counts)
pprTickGroup :: NonEmpty (Tick, Int) -> SDoc
pprTickGroup :: NonEmpty (Tick, Int) -> SDoc
pprTickGroup group :: NonEmpty (Tick, Int)
group@((Tick
tick1,Int
_) :| [(Tick, Int)]
_)
= SDoc -> Int -> SDoc -> SDoc
hang (forall doc. IsLine doc => Int -> doc
int (forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> b
snd NonEmpty (Tick, Int)
group)) forall doc. IsLine doc => doc -> doc -> doc
<+> Tick -> SDoc
pprTickType Tick
tick1)
Int
2 (forall doc. IsDoc doc => [doc] -> doc
vcat [ forall doc. IsLine doc => Int -> doc
int Int
n forall doc. IsLine doc => doc -> doc -> doc
<+> Tick -> SDoc
pprTickCts Tick
tick
| (Tick
tick,Int
n) <- forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (forall a. a -> Down a
Down forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) (forall a. NonEmpty a -> [a]
NE.toList NonEmpty (Tick, Int)
group)])
data Tick
= PreInlineUnconditionally Id
| PostInlineUnconditionally Id
| UnfoldingDone Id
| RuleFired FastString
| LetFloatFromLet
| EtaExpansion Id
| EtaReduction Id
| BetaReduction Id
| CaseOfCase Id
| KnownBranch Id
| CaseMerge Id
| AltMerge Id
| CaseElim Id
| CaseIdentity Id
| FillInCaseDefault Id
| SimplifierDone
instance Outputable Tick where
ppr :: Tick -> SDoc
ppr Tick
tick = Tick -> SDoc
pprTickType Tick
tick forall doc. IsLine doc => doc -> doc -> doc
<+> Tick -> SDoc
pprTickCts Tick
tick
instance Eq Tick where
Tick
a == :: Tick -> Tick -> Bool
== Tick
b = case Tick
a Tick -> Tick -> Ordering
`cmpTick` Tick
b of
Ordering
EQ -> Bool
True
Ordering
_ -> Bool
False
instance Ord Tick where
compare :: Tick -> Tick -> Ordering
compare = Tick -> Tick -> Ordering
cmpTick
tickToTag :: Tick -> Int
tickToTag :: Tick -> Int
tickToTag (PreInlineUnconditionally Id
_) = Int
0
tickToTag (PostInlineUnconditionally Id
_) = Int
1
tickToTag (UnfoldingDone Id
_) = Int
2
tickToTag (RuleFired FastString
_) = Int
3
tickToTag Tick
LetFloatFromLet = Int
4
tickToTag (EtaExpansion Id
_) = Int
5
tickToTag (EtaReduction Id
_) = Int
6
tickToTag (BetaReduction Id
_) = Int
7
tickToTag (CaseOfCase Id
_) = Int
8
tickToTag (KnownBranch Id
_) = Int
9
tickToTag (CaseMerge Id
_) = Int
10
tickToTag (CaseElim Id
_) = Int
11
tickToTag (CaseIdentity Id
_) = Int
12
tickToTag (FillInCaseDefault Id
_) = Int
13
tickToTag Tick
SimplifierDone = Int
16
tickToTag (AltMerge Id
_) = Int
17
pprTickType :: Tick -> SDoc
pprTickType :: Tick -> SDoc
pprTickType (PreInlineUnconditionally Id
_) = forall doc. IsLine doc => String -> doc
text String
"PreInlineUnconditionally"
pprTickType (PostInlineUnconditionally Id
_)= forall doc. IsLine doc => String -> doc
text String
"PostInlineUnconditionally"
pprTickType (UnfoldingDone Id
_) = forall doc. IsLine doc => String -> doc
text String
"UnfoldingDone"
pprTickType (RuleFired FastString
_) = forall doc. IsLine doc => String -> doc
text String
"RuleFired"
pprTickType Tick
LetFloatFromLet = forall doc. IsLine doc => String -> doc
text String
"LetFloatFromLet"
pprTickType (EtaExpansion Id
_) = forall doc. IsLine doc => String -> doc
text String
"EtaExpansion"
pprTickType (EtaReduction Id
_) = forall doc. IsLine doc => String -> doc
text String
"EtaReduction"
pprTickType (BetaReduction Id
_) = forall doc. IsLine doc => String -> doc
text String
"BetaReduction"
pprTickType (CaseOfCase Id
_) = forall doc. IsLine doc => String -> doc
text String
"CaseOfCase"
pprTickType (KnownBranch Id
_) = forall doc. IsLine doc => String -> doc
text String
"KnownBranch"
pprTickType (CaseMerge Id
_) = forall doc. IsLine doc => String -> doc
text String
"CaseMerge"
pprTickType (AltMerge Id
_) = forall doc. IsLine doc => String -> doc
text String
"AltMerge"
pprTickType (CaseElim Id
_) = forall doc. IsLine doc => String -> doc
text String
"CaseElim"
pprTickType (CaseIdentity Id
_) = forall doc. IsLine doc => String -> doc
text String
"CaseIdentity"
pprTickType (FillInCaseDefault Id
_) = forall doc. IsLine doc => String -> doc
text String
"FillInCaseDefault"
pprTickType Tick
SimplifierDone = forall doc. IsLine doc => String -> doc
text String
"SimplifierDone"
pprTickCts :: Tick -> SDoc
pprTickCts :: Tick -> SDoc
pprTickCts (PreInlineUnconditionally Id
v) = forall a. Outputable a => a -> SDoc
ppr Id
v
pprTickCts (PostInlineUnconditionally Id
v)= forall a. Outputable a => a -> SDoc
ppr Id
v
pprTickCts (UnfoldingDone Id
v) = forall a. Outputable a => a -> SDoc
ppr Id
v
pprTickCts (RuleFired FastString
v) = forall a. Outputable a => a -> SDoc
ppr FastString
v
pprTickCts Tick
LetFloatFromLet = forall doc. IsOutput doc => doc
Outputable.empty
pprTickCts (EtaExpansion Id
v) = forall a. Outputable a => a -> SDoc
ppr Id
v
pprTickCts (EtaReduction Id
v) = forall a. Outputable a => a -> SDoc
ppr Id
v
pprTickCts (BetaReduction Id
v) = forall a. Outputable a => a -> SDoc
ppr Id
v
pprTickCts (CaseOfCase Id
v) = forall a. Outputable a => a -> SDoc
ppr Id
v
pprTickCts (KnownBranch Id
v) = forall a. Outputable a => a -> SDoc
ppr Id
v
pprTickCts (CaseMerge Id
v) = forall a. Outputable a => a -> SDoc
ppr Id
v
pprTickCts (AltMerge Id
v) = forall a. Outputable a => a -> SDoc
ppr Id
v
pprTickCts (CaseElim Id
v) = forall a. Outputable a => a -> SDoc
ppr Id
v
pprTickCts (CaseIdentity Id
v) = forall a. Outputable a => a -> SDoc
ppr Id
v
pprTickCts (FillInCaseDefault Id
v) = forall a. Outputable a => a -> SDoc
ppr Id
v
pprTickCts Tick
_ = forall doc. IsOutput doc => doc
Outputable.empty
cmpTick :: Tick -> Tick -> Ordering
cmpTick :: Tick -> Tick -> Ordering
cmpTick Tick
a Tick
b = case (Tick -> Int
tickToTag Tick
a forall a. Ord a => a -> a -> Ordering
`compare` Tick -> Int
tickToTag Tick
b) of
Ordering
GT -> Ordering
GT
Ordering
EQ -> Tick -> Tick -> Ordering
cmpEqTick Tick
a Tick
b
Ordering
LT -> Ordering
LT
cmpEqTick :: Tick -> Tick -> Ordering
cmpEqTick :: Tick -> Tick -> Ordering
cmpEqTick (PreInlineUnconditionally Id
a) (PreInlineUnconditionally Id
b) = Id
a forall a. Ord a => a -> a -> Ordering
`compare` Id
b
cmpEqTick (PostInlineUnconditionally Id
a) (PostInlineUnconditionally Id
b) = Id
a forall a. Ord a => a -> a -> Ordering
`compare` Id
b
cmpEqTick (UnfoldingDone Id
a) (UnfoldingDone Id
b) = Id
a forall a. Ord a => a -> a -> Ordering
`compare` Id
b
cmpEqTick (RuleFired FastString
a) (RuleFired FastString
b) = FastString
a FastString -> FastString -> Ordering
`uniqCompareFS` FastString
b
cmpEqTick (EtaExpansion Id
a) (EtaExpansion Id
b) = Id
a forall a. Ord a => a -> a -> Ordering
`compare` Id
b
cmpEqTick (EtaReduction Id
a) (EtaReduction Id
b) = Id
a forall a. Ord a => a -> a -> Ordering
`compare` Id
b
cmpEqTick (BetaReduction Id
a) (BetaReduction Id
b) = Id
a forall a. Ord a => a -> a -> Ordering
`compare` Id
b
cmpEqTick (CaseOfCase Id
a) (CaseOfCase Id
b) = Id
a forall a. Ord a => a -> a -> Ordering
`compare` Id
b
cmpEqTick (KnownBranch Id
a) (KnownBranch Id
b) = Id
a forall a. Ord a => a -> a -> Ordering
`compare` Id
b
cmpEqTick (CaseMerge Id
a) (CaseMerge Id
b) = Id
a forall a. Ord a => a -> a -> Ordering
`compare` Id
b
cmpEqTick (AltMerge Id
a) (AltMerge Id
b) = Id
a forall a. Ord a => a -> a -> Ordering
`compare` Id
b
cmpEqTick (CaseElim Id
a) (CaseElim Id
b) = Id
a forall a. Ord a => a -> a -> Ordering
`compare` Id
b
cmpEqTick (CaseIdentity Id
a) (CaseIdentity Id
b) = Id
a forall a. Ord a => a -> a -> Ordering
`compare` Id
b
cmpEqTick (FillInCaseDefault Id
a) (FillInCaseDefault Id
b) = Id
a forall a. Ord a => a -> a -> Ordering
`compare` Id
b
cmpEqTick Tick
_ Tick
_ = Ordering
EQ