[GHC] #14013: Bad monads performance
GHC
ghc-devs at haskell.org
Tue Aug 1 14:39:18 UTC 2017
#14013: Bad monads performance
-------------------------------------+-------------------------------------
Reporter: danilo2 | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler | Version: 8.2.1-rc3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by simonpj):
Sigh. This has turned out to be much nastier than I expected. I worked
solely on
{{{
import qualified Control.Monad.State.Strict as Strict
import qualified Control.Monad.State.Class as State
mtlStateListParser_a :: State.MonadState [Char] m => m Bool
mtlStateListParser_a = State.get >>= \case
'a':s -> State.put s >> mtlStateListParser_a
[] -> return True
_ -> return False
{-# INLINE mtlStateListParser_a #-}
foo :: [Char] -> Bool
foo = Strict.evalState mtlStateListParser_a
}}}
I'll refer to `mtlStateListParser_a` as `msp`.
* Yes, comment:9 is right; the right path is to make `doFloatFromRhs`
return `False` for bindings with a stable unfolding.
* Even when that is done, the occurrence analyser does a bad job. We get
{{{
Rec { msp = ... lvl ...
{-# INLINE = ..msp.. #-} -- The stable unfolding
lvl = ...msp...
}
}}}
The occurrence analyser treats the occurrence of `lvl` as a "weak"
reference, and so sorts into SCCs thus: `Rec{ msp }, NonRec { lvl }`. So
then it stupidly marks `msp` as a loop breaker, and `lvl` as a weak loop
breaker. In this case they'd be better in one SCC, in which case we'd
pick `msp` (but not `lvl`) as a loop breaker. The relevant change is in
`OccurAnal`, around line 1280.
{{{
-- Find the "nd_inl" free vars; for the loop-breaker phase
inl_fvs = udFreeVars bndr_set rhs_usage1 `unionVarSet`
case mb_unf_uds of
Nothing -> emptyVarSet -- udFreeVars bndr_set rhs_usage1
-- No INLINE, use RHS
Just unf_uds -> udFreeVars bndr_set unf_uds
}}}
But I'm not fully confident of this change.
* Even if we fix that, then the strictness analyser fails. We end up with
{{{
msp = (\ (s::[Char]). case s of
p1 -> (False, x)
p2 -> (msp |> sym co) s'
) |> co
}}}
Those casts are enough to kill demand analysis. It was relying on the
coercion-floating that we nuked in comment:9! The function looks to the
demand analyser as if it has arity zero, and so we get no useful
strictness.
Yes, we could teach the demand analyser more tricks, but the tail is
beginning to wag the dog.
* This is all stupid. An INILNE pragma on a recursive function is doing
no good at all. Maybe we should just discard it. And indeed that makes
things work.
* Until you use an INLINABLE pragma! We don't want to discard the
INLINEABLE pragama on a recursive function -- it is super-useful. But if
we don't the same ills happen as with INLINE.
Actually, the specialiser propagates an INLINE pragma to the specialised
function, but does '''not''' propagate an INLINEABLE pragam. Result: if
you give an overloaded signature for `msp`, the specialiser will create a
pragma-free specialised version, which will optimise nicely. But if you
give a non-overloaded signature `msp :: Strict.State [Char] Bool`, the
function fails to optimise for the reasons above. Mind you, in the latter
case the INLINEABLE pragma is just as useless as the INLINE pragma was.
This is ridiculously terrible. The pragmas(which are there to optimise
the program) are getting in the way of optimising the function itself.
What to do?
Here's a simple idea;
* Discard INLINE pragmas for recursive, or mutually recursive, functions.
(You can do this manually too!)
* Peel off a top-level function for INLINEABLE pragmas, thus:
{{{
Rec { f = e[f] {-# INLINEABLE = e[f] #-} }
===>
Rec { f' = e[f'] }
Rec { f = f' {-# INLINEABLE = e[f] #-} }
}}}
The first `Rec` is a pragma-free group. The second has all its pragmas
(for later clients), but just indirect to the first group if you actually
call it.
Alas, you can't do this manually right now.
But somehow none of this really feels right. I'm not sure what to do, so
I'm just brain-dumping this. Maybe someone else will have better ideas
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14013#comment:11>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list