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-boun...@haskell.org> On Behalf Of Harendra Kumar
Sent: 06 September 2021 14:11
To: ghc-devs@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


_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Reply via email to