[GHC] #11272: Overloaded state-monadic function is not specialised
GHC
ghc-devs at haskell.org
Mon Dec 21 10:22:30 UTC 2015
#11272: Overloaded state-monadic function is not specialised
-------------------------------------+-------------------------------------
Reporter: NickSmallbone | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.3
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Runtime
Unknown/Multiple | performance bug
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I have a simple typeclass-polymorphic function which fails to specialise.
Here is module A which defines the function `overloaded`:
{{{#!hs
module A where
import Control.Monad.Trans.State
import Control.Monad
overloaded :: Ord a => a -> a -> State () ()
overloaded x y = do
() <- get
when (x <= y) (overloaded y x)
}}}
In module B I use `overloaded` on `Int`s:
{{{#!hs
module B where
import A
import Control.Monad.Trans.State
specialised :: Int -> Int -> ()
specialised x y = execState (A.overloaded x y) ()
}}}
Unfortunately the generated code is not specialised but passes an `Ord`
dictionary around. It doesn't make any difference if I mark `overloaded`
as `INLINEABLE` or not.
In the core file, `overloaded` has been worker-wrapper transformed but the
worker is marked `INLINEABLE[0]` - so I'm not sure why it's not being
specialised. Curiously, if I make `overloaded` be a normal function
instead of one in the state monad, or if I replace `() <- get` with simply
`get`, specialisation goes through fine.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11272>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list