#4227: Allow SPECIALISE pragmas for functions defined in another module
---------------------------------+------------------------------------------
    Reporter:  simonpj           |        Owner:              
        Type:  bug               |       Status:  new         
    Priority:  normal            |    Milestone:              
   Component:  Compiler          |      Version:  6.12.3      
    Keywords:                    |   Difficulty:              
          Os:  Unknown/Multiple  |     Testcase:              
Architecture:  Unknown/Multiple  |      Failure:  None/Unknown
---------------------------------+------------------------------------------
 See http://www.haskell.org/pipermail/glasgow-haskell-
 users/2010-July/019042.html
 {{{
 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`?  Currently no.

 Some care would be needed to support this.  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.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4227>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to