[GHC] #12463: SPECIALIZABLE pragma?

GHC ghc-devs at haskell.org
Tue Sep 27 22:21:27 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:                    |
-------------------------------------+-------------------------------------

Comment (by bgamari):

 Here is a only-slightly-silly example demonstrating a typical case where
 an unsuspecting application author is bitten by the poor performance due
 to missing unfoldings,
 {{{#!hs
 -- File: Lib.hs
 module Lib where
 import Data.Binary
 import Data.Binary.Get
 import Control.Applicative
 import Control.Monad

 -- | Here we have a combinator carefully crafted with an
 -- INLINEABLE pragma by a library author to ensure that the
 -- @Binary a@ dictionary is statically resolved.
 aDecoder :: Binary a => Get ([Int], a)
 aDecoder = (,) <$> replicateM 4 get <*> get
 {-# INLINEABLE aDecoder #-}


 -- File: User.hs
 module User where
 import Data.Binary
 import Control.Monad
 import Lib

 -- | Here an unsuspecting application author tries to use aDecoder
 user1 :: Binary a => Get [([Int], a)]
 user1 = replicateM 5 aDecoder
 --{-# INLINEABLE user1 #-}
 -- If the user forgets this INLINEABLE pragma then the library
 -- author's care is all for naught; the user's program will be
 -- a lumbering, allocating beast for reasons he has no understanding of


 -- File: Main.hs
 {-# LANGUAGE TypeApplications #-}
 import qualified Data.ByteString.Lazy as BS
 import Data.Binary.Get
 import User1

 -- Here is the final callsite where the user instantiates
 -- @a@
 main :: IO ()
 main = do
     bs <- BS.getContents
     print $ runGetOrFail (user1 @Int) bs
 }}}

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12463#comment:10>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list