专门针对相关的多态函数而不进行内联

jbe*_*man 6 performance haskell inline ghc

这是一个简单的例子,重现了我正在研究的一个真正的问题:

一个库模块:

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
Run Code Online (Sandbox Code Playgroud)

另一个,可能由用户定义:

module S where

import Lib

newtype Foo = Foo Int
    deriving Show

instance S Foo where
  mix (Foo x) y = Foo (x+y)
Run Code Online (Sandbox Code Playgroud)

我们的Main:

module Main where

import Lib
import S

import Criterion.Main

main = defaultMain [
    bench "foo" $ whnf (hash (Foo 1)) (2::Int,3::Int)
  ]
Run Code Online (Sandbox Code Playgroud)

用ghc 8.0.1编译ghc --make -Wall -O2 -rtsopts -ddump-to-file -ddump-simpl -dsuppress-module-prefixes -dsuppress-uniques -ddump-core-stats -ddump-inlinings -fforce-recomp Main.hs.

上述基准测试运行时间为4μs.但是,如果我们将INLINEpragma放在两个hash声明中,Lib我们会看到我们想要的预期特化,并获得66 ns的运行时间.

但我真的不想内联所有内容(在用户的真实情况下,Main她可能会hash在同一类型上多次调用),我只是希望该功能专门用于用户代码中的每个组合HS实例.

改变INLINEpragma INLINABLE导致旧行为回归(我认为,因为GHC的内联启发式方法仍在发挥作用).然后我尝试添加

{-# SPECIALIZE hash :: H a=> Foo -> a -> Foo #-}
Run Code Online (Sandbox Code Playgroud)

两个MainS模块,但这会产生

Ignoring useless SPECIALISE pragma for class method selector ‘hash’
Run Code Online (Sandbox Code Playgroud)

...警告和相同的错误代码.

一些限制:

  • 虽然不理想但要求每个S实例声明都包含有限数量的pragma(可能与之相关H),这是可以接受的.
  • 同样的 H
  • 要求用户为和的SPECIALIZE每个组合做一个是不可接受的.SH

没有INLINE可以做到这一点吗?

这可能与使用约束专业化和相关的trac票据https://ghc.haskell.org/trac/ghc/ticket/8668相同,但我想我会再次询问并可能将此作为GHC Trac的更简单示例发布.


编辑:继续开了一张ghc票:https://ghc.haskell.org/trac/ghc/ticket/13376