Specialiser changes program's behaviour
I have the following Haskell program:
{-# LANGUAGE MonoLocalBinds #-}
module Main (main) where
class C a where
op :: a -> String
instance {-# OVERLAPPABLE #-} C a where
op _ = "Generic"
{-# NOINLINE op #-}
instance {-# INCOHERENT #-} C () where
op _ = "Specific"
{-# NOINLINE op #-}
{-# NOINLINE large #-}
-- | Inhibit inlining, but keep specialize-ability
large :: a -> a
large x = x
bar :: C a => a -> String
bar x = large (large (large (large (large (large (large (large (large (large (large (large (large (large (op x))))))))))))))
spec :: () -> String
spec = bar
gen :: a -> String
gen = bar
main :: IO ()
main = do
putStrLn $ "spec () == " <> spec ()
putStrLn $ "gen () == " <> gen ()
Because gen
has no typeclass constraint on C a
, the only way to resolve the constraint on bar
is to choose the generic instance. On the other hand, in spec
, we have a more specific instance for C ()
, and so that one should be picked.
Compiling and running without optimizations, this is indeed the behaviour one can observe:
$ ./_build/stage1/bin/ghc -fforce-recomp --make input/overlap3.hs && ./input/overlap3
[1 of 2] Compiling Main ( input/overlap3.hs, input/overlap3.o )
[2 of 2] Linking input/overlap3 [Objects changed]
spec () == Specific
gen () == Generic
However, if we then enable specialisation, something goes wrong. How exactly, depends on the version of GHC.
On and before 8d2dbe2d, we get:
$ ./_build/stage1/bin/ghc -fforce-recomp -fspecialise -fenable-rewrite-rules --make input/overlap3.hs && ./input/overlap3
[1 of 2] Compiling Main ( input/overlap3.hs, input/overlap3.o )
[2 of 2] Linking input/overlap3 [Objects changed]
spec () == Generic
gen () == Generic
But from 5a997e16 onwards, we get the, perhaps even more baffling:
$ ./_build/stage1/bin/ghc -fforce-recomp -fspecialise -fenable-rewrite-rules --make input/overlap3.hs && ./input/overlap3
[1 of 2] Compiling Main ( input/overlap3.hs, input/overlap3.o )
[2 of 2] Linking input/overlap3 [Objects changed]
spec () == Specific
gen () == Specific
The change between these two commits is an overhaul of the specialiser implementation by @simonpj , so it's at least understandable that the behaviour changed at this point.
Edited by sheaf