Skip to content
Snippets Groups Projects
Commit f002250a authored by Andreas Klebinger's avatar Andreas Klebinger Committed by Marge Bot
Browse files

Dont gather ticks when only striping them in STG.

Adds stripStgTicksTopE which only returns the stripped expression.
So far we also allocated a list for the stripped ticks which was
never used.

Allocation difference is as expected very small but present.
About 0.02% difference when compiling with -O.
parent 80afdf6b
No related branches found
No related tags found
No related merge requests found
......@@ -265,7 +265,7 @@ mkRhsClosure dflags bndr _cc
upd_flag -- Updatable thunk
[] -- A thunk
expr
| let strip = snd . stripStgTicksTop (not . tickishIsCode)
| let strip = stripStgTicksTopE (not . tickishIsCode)
, StgCase (StgApp scrutinee [{-no args-}])
_ -- ignore bndr
(AlgAlt _)
......
......@@ -716,7 +716,7 @@ mkTopStgRhs dflags this_mod ccs bndr rhs
, ccs )
where
(_, unticked_rhs) = stripStgTicksTop (not . tickishIsCode) rhs
unticked_rhs = stripStgTicksTopE (not . tickishIsCode) rhs
upd_flag | isUsedOnce (idDemandInfo bndr) = SingleEntry
| otherwise = Updatable
......@@ -758,7 +758,7 @@ mkStgRhs bndr rhs
currentCCS
upd_flag [] rhs
where
(_, unticked_rhs) = stripStgTicksTop (not . tickishIsCode) rhs
unticked_rhs = stripStgTicksTopE (not . tickishIsCode) rhs
upd_flag | isUsedOnce (idDemandInfo bndr) = SingleEntry
| otherwise = Updatable
......
......@@ -50,7 +50,7 @@ module StgSyn (
topStgBindHasCafRefs, stgArgHasCafRefs, stgRhsArity,
isDllConApp,
stgArgType,
stripStgTicksTop,
stripStgTicksTop, stripStgTicksTopE,
stgCaseBndrInScope,
pprStgBinding, pprGenStgTopBindings, pprStgTopBindings
......@@ -163,12 +163,18 @@ stgArgType (StgVarArg v) = idType v
stgArgType (StgLitArg lit) = literalType lit
-- | Strip ticks of a given type from an STG expression
-- | Strip ticks of a given type from an STG expression.
stripStgTicksTop :: (Tickish Id -> Bool) -> GenStgExpr p -> ([Tickish Id], GenStgExpr p)
stripStgTicksTop p = go []
where go ts (StgTick t e) | p t = go (t:ts) e
go ts other = (reverse ts, other)
-- | Strip ticks of a given type from an STG expression returning only the expression.
stripStgTicksTopE :: (Tickish Id -> Bool) -> GenStgExpr p -> GenStgExpr p
stripStgTicksTopE p = go
where go (StgTick t e) | p t = go e
go other = other
-- | Given an alt type and whether the program is unarised, return whether the
-- case binder is in scope.
--
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment