[GHC] #12463: SPECIALIZABLE pragma?
GHC
ghc-devs at haskell.org
Sat Sep 24 21:13:05 UTC 2016
#12463: SPECIALIZABLE pragma?
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner:
Type: feature request | Status: new
Priority: low | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords: Inlining
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by bgamari:
@@ -52,1 +52,1 @@
- # Transitive specialisation
+ = Transitive specialisation =
New description:
Currently it is common practice for library authors to use the
`INLINEABLE` pragma to make it more likely that a polymorphic function
should get an unfolding in the module's interface file to ensure that GHC
is able to specialize. While in practice this works reasonably well, it's
not really saying what we often mean: we don't want to inline, we really
just want GHC to behave like each use-site's module has a `SPECIALISE`
pragma for each concrete type that the function is used at. For instance,
consider,
{{{#!hs
module ALibrary where
aLibraryFunction :: AClass a => a -> a
aLibraryFunction = {- some large expression involving methods of AClass -}
module SomeUser where
import ALibrary
aUser :: Int -> Int
aUser = {- some large expression involving aLibraryFunction -}
}}}
Ideally, we would want GHC to take and produce one specialized version of
`aLibraryFunction` for every concrete type which it is used at. However,
without an `INLINEABLE` function, GHC won't even consider producing an
unfolding for `aLibraryFunction` due to its size. We can only convince GHC
to produce an unfolding for `aLibraryFunction` if we annotate it with an
`INLINEABLE` pragma. While this is often effective, it doesn't really say
what we mean: We don't never want GHC to inline; merely to specialize.
This is issue especially prevalent in code using MTL-style effects, where
we have ubiquitous overloading of very frequently-used functions (e.g.
bind).
Really what we want in this case is a way of indicating to GHC that a
function shouldn't be inlined (use-sites replaced with the body of the
function), but rather that GHC should try hard to specialize away
particular type variables. This might look like,
{{{#!hs
aLibraryFunction :: AClass a => a -> a
aLibraryFunction = {- some large expression involving methods of AClass -}
{-# SPECIALISE(a) forall a. aLibraryFunction :: a -> a #-}
}}}
The list of type binders after `SPECIALISE` is the set of binders which
GHC would attempt to specialize.
This pragma requests that GHC keep an inlining around and produce a
specialized version of `aLibraryFunction` every time it saw a concrete
instantiation of `a`. Moreover, the produced symbols could be declared as
weak, allowing the linker to cull duplicated code when possible.
= Transitive specialisation =
The above `SPECIALISE` pragma still doesn't address the fragility of
specialisation, however. Namely, consider,
{{{#!hs
module ALibrary where
class AClass
instance AClass Int
aLibraryFunction :: AClass a => a -> a
aLibraryFunction = {- some large expression involving methods of AClass -}
{-# SPECIALISE(a) forall a. aLibraryFunction :: a -> a #-}
module AnotherLibrary where
import ALibrary
aFunction :: AClass a => a -> a
aFunction x = {- ... -} aLibraryFunction x {- ... -}
module AUser where
import AnotherLibrary
f = let x :: Int
x = 5
in aFunction x
}}}
Here `aLibraryFunction` may depend crucially on specialisation; however,
the polymorphic user `aFunction` has no way of knowing this and may be too
large for GHC to produce an unfolding automatically. This ultimately means
that GHC will be unable to specialise the eventual instantiation at `Int`
in `AUser.f`. This will mean that the performance characteristics of
`ALibrary` will be rather fragile.
One (admittedly rather heavy) approach to solving this fragility is to
inform GHC that `aLibraryFunction`'s polymorphic callsites should have
unfoldings, ensuring that we are able to specialise the eventual
monomorphic callsite,
{{{#!hs
aLibraryFunction :: AClass a => a -> a
aLibraryFunction = {- some large expression involving methods of AClass -}
{-# SPECIALISE_RECURSIVE(a) forall a. aLibraryFunction :: a -> a #-}
}}}
Which would ensure that polymorphic use-sites of `aLibraryFunction` would
themselves be marked as `SPECIALISE_RECURSIVE`, shielding users from the
need to know about `aLibrarFunction`'s expectations of the simplifier.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12463#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list