SPECIALIZE one of two identical functions does not fire well
Hi,
I am playing with SPECIALIZE
pragma:
module Todo where
{-# SPECIALIZE plusTwoRec :: [Int] -> [Int] #-}
plusTwoRec :: Num a => [a] -> [a]
plusTwoRec [] = []
plusTwoRec (x:xs) = x+2:plusTwoRec xs
plusTwoRec' :: Num a => [a] -> [a]
plusTwoRec' [] = []
plusTwoRec' (x:xs) = x+2:plusTwoRec' xs
And wanted to benchmark it with (in Main.hs
):
import Todo
import Criterion.Main
aListOfInt :: [Int]
aListOfInt = [1..10000]
main :: IO ()
main = defaultMain
[ bench "plusTwoRec" $ nf plusTwoRec aListOfInt
, bench "plusTwoRec'" $ nf plusTwoRec' aListOfInt
]
Sadly, the rule of specialization of plusTwoRec
does not fire in Main.hs
(I compiled with:
ghc Main.hs -O -dynamic -ddump-rule-firings
(the -dynamic
part is due to my ArchLinux installaltion)).
The result is:
[1 of 2] Compiling Todo ( Todo.hs, Todo.o )
Rule fired: Class op + (BUILTIN)
Rule fired: Class op fromInteger (BUILTIN)
Rule fired: integerToInt (BUILTIN)
Rule fired: SPEC plusTwoRec (Todo)
[2 of 2] Compiling Main ( Main.hs, Main.o )
Rule fired: Class op enumFromTo (BUILTIN)
Rule fired: unpack (GHC.Base)
Rule fired: unpack (GHC.Base)
Rule fired: eftIntList (GHC.Enum)
Rule fired: unpack-list (GHC.Base)
Rule fired: unpack-list (GHC.Base)
Linking Main ...
I have inspected a bit the code produced after the simplifications passes (with -ddump-simpl
) and here is the suspicious part:
plusTwoRec :: forall a. Num a => [a] -> [a]
[GblId,
Arity=2,
Caf=NoCafRefs,
Str=<L,U(C(C1(U)),A,A,A,A,A,C(U))><S,1*U>,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=True)}]
plusTwoRec = plusTwoRec'
I believe that plusTwoRec
is inlined before the specialization has a chance to fire, but I am not sure at all !
Separating the two functions definitions in two different files works.
So I don't know if this is a GHC bug, myself that does not read the right part of the GHC manual, if it is only a lack of documentation, or anything else.
Trac metadata
Trac field | Value |
---|---|
Version | 8.4.3 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |