[GHC] #15001: Add strict product field demands to lambda binders
GHC
ghc-devs at haskell.org
Wed Apr 4 16:02:50 UTC 2018
#15001: Add strict product field demands to lambda binders
-------------------------------------+-------------------------------------
Reporter: sgraf | Owner: (none)
Type: task | Status: new
Priority: normal | Milestone: ⊥
Component: Compiler | Version: 8.5
Keywords: DmdAnal | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): D4244 | Wiki Page:
-------------------------------------+-------------------------------------
This is a follow-up on the first improvement in [Phab:D4244#126311].
Consider the following two functions with identical semantics:
{{{
module Foo where
{-# LANGUAGE BangPatterns #-}
data Complex a = !a :+ !a
foo :: Complex Double -> Int -> Complex Double
foo !x 0 = x
foo (a :+ b) _ = b :+ a
bar :: Complex Double -> Int -> Complex Double
bar x 0 = x
bar (a :+ b) _ = b :+ a
}}}
In the corresponding simplified Core, `x` gets strictness `S(SS)` for
`foo`, but only `S` for `bar`. We could do better by looking at `x`s type
and see that its a product type with strict fields.
This is because currently only case binders get
[https://github.com/ghc/ghc/blob/72b5f649ede82ab3bb429aa72ee1c572f415b0eb/compiler/stranal/DmdAnal.hs#L253
special treatment] for strict product fields through
`addDataConStrictness`.
This ticket tracks if the same is worthwhile for lambda binders, as in
`bar` above. Note that intuitively, this shouldn't make any difference
because when we eventually unleash an `S` demand on a `Complex`
constructor, we add `seqDmd` on strict fields anyway, amounting to
`S(SS)`. So this is only a matter of recording things early because some
parts of the analysis code might not be smart enough to add strict field
demands by themselves.
Also note that this doesn't touch impliciations on usage analysis at all,
where unleashing the same `seqDmd` twice might mean we accidentally make
some product field lose its single-entrieness.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15001>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list