SPECIALIZE function for type defined elsewhere

Dear GHC experts, say I have module A where class C a where ... f :: C a => String -> a module B where import A data T = ... instance C T where ... g :: String -> SomeOtherType g s = doSomethingWith (f s) Is it possible to SPECIALIZE `f` for the type `T`? If I put the pragma {-# SPECIALIZE f :: String -> T #-} in module A, GHC complains that `T` is not in scope. If I put it in module B GHC complains that there is no accompanying binding for `f`. In my case, I don't want to put everything in a single module because I cannot know what other B-like modules people will implement. Are they bound to use `f` unspecialized for their types? Why? Cheers, Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

On 28 July 2010 13:57, Sebastian Fischer
In my case, I don't want to put everything in a single module because I cannot know what other B-like modules people will implement.Are they bound to use `f` unspecialized for their types?
Yes. GHC might inline "f" into the call site and achieve specialisation that way, but AFAIK there is no way to force this.
Why?
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. 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. You would probably also want some sort of mechanism to "common up" specialisations if several modules independently specialise one function to the same type (could do this in the linker or even earlier). You would probably also have to be prepared to emit warnings about stuff like this: """ module A where import B f :: Foo a => a -> a f = ... """ """ module B import {-# SOURCE #-} A newtype Bar = ... instance Foo Bar where {-# SPECIALISE f :: Bar -> Bar #-} """ Another nice-to-have along the same lines is something like this: """ map_unboxed :: [Int#] -> [Int#] map_unboxed = map (+# 1) """ i.e. allow polymorphic functions to be instantiated at types of a kind other than *. This would be a rather cool and useful feature :-). As far as I know noone is working on either of these features. Cheers, Max

On Jul 28, 2010, at 5:40 PM, Max Bolingbroke wrote:
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.
Would it be reasonable (and possible) to reject specialization only if the functions used in the body of the specialized version are not in scope? This would be similar to the error one gets when specializing a function for a type wich is not in scope. With this behaviour it might be easy to work around the error by importing all needed functions. Cheers, Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

| 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
participants (3)
-
Max Bolingbroke
-
Sebastian Fischer
-
Simon Peyton-Jones