Specializing related polymorphic functions without inlining
Here's a minimal example reproducing a real problem I'm working on:
One library module:
module Lib where
class H h where
hash :: (S s)=> s -> h -> s
class S s where
mix :: s -> Int -> s
instance (H x, H y)=> H (x,y) where
hash s = (x,y) ->
s `hash` x `hash` y
-- make this look "big":
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
`hash` x `hash` y `hash` x `hash` y `hash` x `hash` y `hash` x `hash` y
instance H Int where
hash s = n -> s `mix` n
Another, possibly defined by a user:
module S where
import Lib
newtype Foo = Foo Int
deriving Show
instance S Foo where
mix (Foo x) y = Foo (x+y)
And our Main :
module Main where
import Lib
import S
import Criterion.Main
main = defaultMain [
bench "foo" $ whnf (hash (Foo 1)) (2::Int,3::Int)
]
Compiling with ghc 8.0.1 with ghc --make -Wall -O2 -rtsopts -ddump-to-file -ddump-simpl -dsuppress-module-prefixes -dsuppress-uniques -ddump-core-stats -ddump-inlinings -fforce-recomp Main.hs .
The benchmark above runs in 4 μs . If however we put INLINE pragmas on the two hash declarations in Lib we see the expected specializations we want and get a runtime of 66 ns .
But I don't really want to inline everything (in the user's real Main she might be calling hash many many times on the same type), I just want the function specialized for every combination of H and S instance in the user's code.
Changing INLINE pragmas to INLINABLE caused a regression to the old behavior (expected I think, since GHC's inlining heuristics are still at play). I then tried adding
{-# SPECIALIZE hash :: H a=> Foo -> a -> Foo #-}
to both Main and S modules but this generates
Ignoring useless SPECIALISE pragma for class method selector ‘hash’
...warnings and the same bad code.
Some constraints:
S instance declaration to include a finite number of pragmas (possibly related to H ) H SPECIALIZE for every combination of S and H . Is it possible to do this without INLINE?
This is probably the same as Specialization with Constraints and related trac ticket https://ghc.haskell.org/trac/ghc/ticket/8668, but I thought I would ask again and possibly post this as a simpler example to the GHC Trac.
EDIT : went ahead and opened a ghc ticket: https://ghc.haskell.org/trac/ghc/ticket/13376
链接地址: http://www.djcxy.com/p/33198.html上一篇: 用GHC保证专业化
下一篇: 专门化没有内联的相关多态函数
