Static data and RULES

David Feuer david.feuer at gmail.com
Thu Feb 16 22:12:43 UTC 2017


Ben Gamari and Reid Barton are interested in making it cheaper for static
data to pass through simplification. The basic idea is that if a term is
already made entirely of data constructors and literals, then there's
nothing left to optimize.

However, RULES are allowed to match on data constructors and it would be
nice to let that keep happening. But on the other hand, RULES are
apparently (according to Duncan Coutts) already broken for strict data
constructors, because they have workers and wrappers.

My thought: let's allow phased INLINE and NOINLINE pragmas for data
constructors. The default would be INLINE. The ~ phase choice would not be
available: once inline, always inline.

Semantics
~~~~~~~~~~

For all constructors:

If a constructor is allowed by pragmas to inline in a certain phase, then
in that phase terms built from it can be considered static. Once static,
always static.

If a constructor is not allowed to inline in a certain phase, terms built
from it will be considered non-static.

After demand analysis and worker/wrapper, all constructors are considered
inline.

For strict constructors:

A strict constructor wrapper prohibited from inlining in a certain phase
simply will not.

Strict constructor wrappers will all be allowed to inline after demand
analysis and worker/wrapper. This matches the way we now handle wrappers
actually created in that phase.

Syntax:

For GADT syntax, this is easy:

data Foo ... where
  {-# INLINE [1] Bar #-}
  Bar :: ...

For traditional syntax, I think it's probably best to pull the pragmas to
the top:

{-# NOINLINE Quux #-}
data Baz ... = Quux ... | ...
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20170216/527311d5/attachment-0001.html>


More information about the ghc-devs mailing list