SPECIALIZE function for type defined elsewhere

Simon Peyton-Jones simonpj at microsoft.com
Wed Jul 28 12:01:56 EDT 2010


| SPECIALISE pragmas are not supported in any but the defining module
| because the Core for a function to specialise is not guaranteed to be
| available in any other module. I don't think there is any other
| barrier.

Yes, exactly.

| It is possible to imagine implementing a remedy for this by using
| -fexpose-all-unfoldings and having GHC use the exposed Core to
| generate a specialisation in any importing module.

Indeed, I've often thought of such a feature.  It would be a Good Thing.

But some care would be needed.  Currently GHC's "-fexpose-all-unfoldings" makes no attempt to ensure that the exposed unfolding for f is exactly what the user originally wrote.  For example, other functions might  have been inlined into f's RHS that might make it a lot bigger.  Maybe you'd want to say

	{-# SPECIALISABLE f #-}
	f = <blah>

to mean "expose f's unfolding, pretty much as-is, rather than optimising it".  This is close to what you get with

	{-# INLINE f #-}

(which also exposes the original RHS) but without the "please inline me at every call site" meaning.  Hmm.  Oh if I had more time.

But as of today, no it just isn't supported.  Another ticket! http://hackage.haskell.org/trac/ghc/ticket/4227

Simon


More information about the Glasgow-haskell-users mailing list