Question about specialization
Simon Peyton Jones
simonpj at microsoft.com
Mon Sep 6 14:47:40 UTC 2021
Harendra
That comes as a surprise to me. Could you possibly make a repo case, and say what version of the compiler does, and does not, specialise the function?
File it as a ticket … to me it looks like a bug.
Thanks
Simon
From: ghc-devs <ghc-devs-bounces at haskell.org> On Behalf Of Harendra Kumar
Sent: 06 September 2021 14:11
To: ghc-devs at haskell.org
Subject: Question about specialization
Hi GHC devs,
I have a simple program using the streamly library, as follows, the whole code is in the same module:
{-# INLINE iterateState #-}
{-# SPECIALIZE iterateState :: Int -> SerialT (StateT Int IO) Int #-}
iterateState :: MonadState Int m => Int -> SerialT m Int
iterateState n = do
x <- get
if x > n
then do
put (x - 1)
iterateState n
else return x
main :: IO ()
main = do
State.evalStateT (S.drain (iterateState 0)) 100000
Earlier the SPECIALIZE pragma was not required on iterateState, but after some refactoring in the library (the monad bind of SerialT changed a bit), this program now requires a SPECIALIZE on iterateState to trigger specialization, just INLINE also does not help.
My question is whether this may be expected in some conditions or is this something which can be considered a bug in the compiler? I am also curious what specifically could have made the compiler not specialize this anymore, is it the size of the function or some other threshold?
Thanks,
Harendra
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20210906/a6032ecb/attachment.html>
More information about the ghc-devs
mailing list