A performance predicament
Simon Peyton Jones
simonpj at microsoft.com
Fri Mar 11 17:04:54 UTC 2016
You don't say how you got those numbers, but if it's by -prof-auto-all it may be a red herring. Profiling prevents optimisation!
I built TcFlatten by touching it, make, grab command line, then execute that command line again with -ddump-simpl.
The defn of >>= for FlatM looks scary (below); but it's never called because it's already been inlined. So I don’t think it'll allocate anything.
An alternative approach is to add manual SCCs and drill in gradually
Simon
TcFlatten.$fMonadFlatM1 =
\ (@ a11_abat)
(@ b_abau)
(m_a7hJ :: FlatM a11_abat)
(k_a7hK :: a11_abat -> FlatM b_abau)
(env_a7hL :: FlattenEnv) ->
let {
m1_aegb [Dmd=<L,C(U)>] :: TcS a11_abat
[LclId, Str=DmdType]
m1_aegb = (m_a7hJ `cast` ...) env_a7hL } in
(\ (ebs_aegd :: TcSMonad.TcSEnv) ->
let {
eta_aege [Dmd=<L,C(C(U(U,U)))>]
:: IOEnv.IOEnv (Env TcGblEnv TcLclEnv) a11_abat
[LclId, Str=DmdType]
eta_aege = (m1_aegb `cast` ...) ebs_aegd } in
(\ (eta2_aegf :: Env TcGblEnv TcLclEnv)
(eta3_aegg [OS=OneShot]
:: ghc-prim-0.4.0.0:GHC.Prim.State#
ghc-prim-0.4.0.0:GHC.Prim.RealWorld) ->
case (((eta_aege `cast` ...) eta2_aegf) `cast` ...) eta3_aegg
of _ [Occ=Dead] { (# ipv_aegj, ipv1_aegk #) ->
((((((((k_a7hK ipv1_aegk) `cast` ...) env_a7hL) `cast` ...)
ebs_aegd)
`cast` ...)
eta2_aegf)
`cast` ...)
ipv_aegj
})
`cast` ...)
`cast` ...
| -----Original Message-----
| From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of
| Richard Eisenberg
| Sent: 11 March 2016 16:12
| To: ghc-devs at haskell.org developers <ghc-devs at haskell.org>
| Subject: A performance predicament
|
| Hi devs,
|
| I'm working on some compiler performance bugs. I've implemented caching
| for coercion kinds at Phab:D1992. But tests show a net slowdown, which
| I'm currently investigating. I could abandon this work for 8.0, but it
| really should show an improvement, and so I'm looking deeper.
|
| A little profiling has shown that the (>>=) operator of the FlatM monad
| is doing 13% of all allocations on a test program (T3064). The sad
| thing is that, if I understand correctly, this bind shouldn't do any
| allocation at all! Here are the relevant definitions:
|
| > newtype FlatM a = FlatM { runFlatM :: FlattenEnv -> TcS a }
| > newtype TcS a = TcS { unTcS :: TcSEnv -> TcM a }
| > type TcM = TcRn
| > type TcRn = TcRnIf TcGblEnv TcLclEnv
| > type TcRnIf a b = IOEnv (Env a b)
| > newtype IOEnv env a = IOEnv (env -> IO a)
|
| As we can see here, FlatM a is equivalent to (Foo -> Bar -> Baz -> IO
| a). So working in this monad should just pass around the three
| parameters without doing any allocation, unless IO's bind operation
| does allocation. (I assume we use magic to prevent that last piece.)
| I've tried adding INLINE to the various pieces to no avail.
|
| Am I misunderstanding something fundamental here? I feel like I must
| be.
|
| Thanks,
| Richard
|
| PS: The allocation done by FlatM was around before my caching
| optimization. So I'm working slightly orthogonally to where I started.
| But if IOEnv is really doing something even slightly slowly, a small
| tweak here could net massive improvements in overall speed.
| _______________________________________________
| ghc-devs mailing list
| ghc-devs at haskell.org
| https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.ha
| skell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
| devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c08f2a6ba49224e52
| f77108d349c7e37e%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=tIy8Et5RN
| MpnOmPbypf7ggBq6DgufBd%2bACe46nau%2b%2fk%3d
More information about the ghc-devs
mailing list