Hi Simon.
Thanks for the reply. Below, I try to explain more clearly what I want and why below. If it’s still murky, and if you’re up for it, a Skype chat would probably help a lot.
I think I’m looking for something very close to GHC’s specialization
as it is now, and I’m wondering how to best leverage the specialization
that GHC already does. I have a GHC plugin that transforms Core programs
into reifying versions of themselves. The transformation is triggered
by application of a “function” reify ∷ a → E a
for an expression GADT). reify
is more like a macro, in that its implementation relies on the (Core)
syntax of its argument, not just its semantics, but in a well-behaved
way (with a simple, non-syntactic specification). This reifying
transformation benefits from the dictionary elimination that GHC’s
specializer performs, and I’d like to benefit more. After
specialization, or as part of it, I want to reuse the work of reifying
the specialized definition. Currently I have to inline the code
generated by the specializer, across modules (and assuming that its code
is available), and then reify it at each call site. I’d rather have the
option to reify specializations in the defining module and then reuse
those reified specializations at call-sites, even in other modules.
Thus, I don’t want to specialize a function foo
at various types, but the result of transforming reify foo
for those types, hence my interest in specializing expressions at least
a bit more complicated than identifiers. I expect that this scheme, or
something like it, will let me eliminate much inlining of code from
other modules and then reifying these large expressions. In other words,
it lets me do “separate reification” akin to separate compilation.
Perhaps I should be thinking of specializing reifications instead of
reifying specializations. I guess that alternative would mean having the
specializer perform reification (using a few CoreExpr
rewrites) as part of the work it does. Given foo ∷ T
(where T
may include polymorphism and dictionaries), I might generate
reify_foo ∷ E T
reify_foo = reify foo
and then transform the RHS to remove the reify
call, resulting in E
-building Core code. Then request specializations for reify_foo
.
The types are not quite this simple, due to polymorphism and dictionaries. For instance, given
sum ∷ (Foldable f, Num a) ⇒ f a → a
generate
reify_sum ∷ (Foldable f, Num a) ⇒ E (f a → a)
reify_sum = reify sum
In Core,
reify_sum ∷ ∀ f a. Foldable f → Num a → E (f a → a)
reify_sum = λ (@ f) (@ a) ($dFoldable ∷ Foldable f) ($dNum ∷ Num a)
→ reify (sum @ f @ a $dFoldable $dNum)
Then ask for specializations of reify_sum
. Since reification all happens invisibly, reify_sum
won’t ever get called in client code. Instead, I’d have to also recognize calls to reify sum
from other modules and replace those calls with reify_sum
.
Oh. Hm. Perhaps the specializer doesn’t have to invoke the reifier after all. Maybe I can generate definitions like reify_sum
and some SPECIALIZE
pragmas (or directly invoke the equivalent code GHC), and then reify the results after the specializer runs.
I’ve started down a path of doing something similar:
reify
rules that use those new definitions (as the specializer does). Here’s
where I’m worried about the efficiency of having many rules with the
same RHS top-level identifier.reify
calls inward where they can meet up with other functions also reify
rules from other modules.Because I’m worried about the performance with many reify
rules, maybe I’ll drop the rules and instead export definitions like reify_sum
(after reify
-transforming
the RHS), with predictable names, and then explicitly look for those
names across modules during reification. Or does GHC handle that
situation well, as long there are few uses (probably only one use) of
each name that reify
is applied to in these rules (thanks to the specializer having already run, yielding many differently named specializations).
As I mentioned, a Skype chat may be helpful.
Best regards, - Conal
I’m sorry Conal I’m not getting this.
Specialisation happens when you have a named chunk of code that is repeatedly called at different types, and with different args. We can inline it bodily to specialise to that one call site, but it’s cooler to make a single specialised version which can be shared among many call sites. (And that approach deals with recursive functions too.)
But that explanation is fundamentally about named functions, so I don’t understand this “general expression” bit. Sorry!
Simon
From: ghc-devs [mailto:ghc-devs-bounces@haskell.org] On Behalf Of Conal Elliott
Sent: 01 February 2016 01:16
To: ghc-devs@haskell.org
Subject: Re: Specializing expressions beyond names?
A related question: if there are a great many rules of the form "reify (foo ...) = ...", where 'reify' is always present (and the outermost application head) but for many different argument expressions, will rule matching be linear (expensive) in the number of such rules?
-- Conal
On Sun, Jan 31, 2016 at 1:58 PM, Conal Elliott <conal@conal.net> wrote:
It seems to be the case that
SPECIALIZE
pragmas are syntactically restricted to type specializations of a name (identifier) rather than a general expression. Is my understanding correct here? If so, is there any reason for this restriction?I ask because I’m reifying Core code (into code that constructs a corresponding run-time representation for further processing), and I’m looking for a clean way to integrate that process with GHC, to support separate compilation and to avoid interfering with GHC’s regular flow. It occurred to me that I could enable separate compilation via a pragma of the form “
{-# SPECIALIZE reify foo
∷
E t #-}
” for somet
, whereE t
is a reified form of values of typet
. Type checking would infer the specialized type offoo
, and the usual specialization phase would do its usual thing on that specialization, leaving “reify foo = reify specialized_foo
”, and then the reification compiler plugin would transform the right-hand side, pushing thereify
inward. Somereify
calls may remain (e.g., due to polymorphism), triggering future rule applications. As much as possible of the fully-reified version would be factored out of the generated rule’s RHS for cheap reuse.
Thanks, - Conal