SPECIALIZE function for type defined elsewhere

Sebastian Fischer sebf at informatik.uni-kiel.de
Wed Jul 28 08:57:07 EDT 2010


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.)





More information about the Glasgow-haskell-users mailing list