问题描述
我有一个正在尝试优化的功能.这是较大代码的一部分,我怀疑该函数阻止 GHC
在调用它的更高级别函数中对 Int
参数取消装箱.因此,我编写了一个简单的测试,并牢记了两点:理解核心,并尝试不同的方法以查看是什么使GHC拆箱,以便将课程应用于更大的代码.这是带有 test
函数包装的函数 cmp
:
I have a function that I am trying to optimize. This is part of a bigger code where I suspect this function is preventing GHC
from unboxing Int
arguments at higher level function that calls it. So, I wrote a simple test with two things in mind - understand the core, and try different things to see what makes GHC unbox it, so that I can apply the lessons to bigger code. Here is the function cmp
with a test
function wrapper:
{-# LANGUAGE BangPatterns #-}
module Cmp
( cmp,
test )
where
import Data.Vector.Unboxed as U hiding (mapM_)
import Data.Word
cmp :: (U.Unbox a, Eq a) => U.Vector a -> U.Vector a -> Int -> Int -> Int
cmp a b !i !j = go a b 0 i j
where
go v1 v2 !len !i !j| (i<n) && (j<m) && ((unsafeIndex v1 i) == (unsafeIndex v2 j)) = go v1 v2 (len+1) (i+1) (j+1)
| otherwise = len
where
n = U.length a
m = U.length b
{-# INLINABLE cmp #-}
test :: (U.Unbox a, Eq a) => U.Vector a -> U.Vector a -> U.Vector Int -> Int
test a b i = U.sum $ U.map (\x -> cmp a b x x) i
理想情况下, test
应该使用以下签名调用未装箱的 cmp
版本(当然,如果我错了,请纠正我):
Ideally, test
should call unboxed version of cmp
with following signature (of course, correct me if I am wrong):
U.Vector a -> U.Vector a -> Int# -> Int# -> Int#
查看在 ghc 7.6.1
中生成的核心(命令行选项: ghc -fforce-recomp -ddump-simpl -dsuppress-uniques -dsuppress-idinfo -dsuppress-module-前缀-O2 -fllvm
),我在 test
的内部循环中看到了这一点-来自以下核心的代码段,并添加了我的注释:
Looking at the core generated in ghc 7.6.1
(command line option:ghc -fforce-recomp -ddump-simpl -dsuppress-uniques -dsuppress-idinfo -dsuppress-module-prefixes -O2 -fllvm
), I see this for inner loop for test
- snippets from core below, with my comments added:
-- cmp function doesn't have any helper functions with unboxed Int
--
cmp
:: forall a.
(Unbox a, Eq a) =>
Vector a -> Vector a -> Int -> Int -> Int
...
-- This is the function that is called by test - it does keep the result
-- unboxed, but calls boxed cmp, and unboxes the result of cmp (I# y)
--
$wa
:: forall a.
(Unbox a, Eq a) =>
Vector a -> Vector a -> Vector Int -> Int#
$wa =
\ (@ a)
(w :: Unbox a)
(w1 :: Eq a)
(w2 :: Vector a)
(w3 :: Vector a)
(w4 :: Vector Int) ->
case w4
`cast` (<TFCo:R:VectorInt> ; <NTCo:R:VectorInt>
:: Vector Int ~# Vector Int)
of _ { Vector ipv ipv1 ipv2 ->
letrec {
$s$wfoldlM'_loop :: Int# -> Int# -> Int#
$s$wfoldlM'_loop =
\ (sc :: Int#) (sc1 :: Int#) ->
case >=# sc1 ipv1 of _ {
False ->
case indexIntArray# ipv2 (+# ipv sc1) of wild { __DEFAULT ->
let {
x :: Int
x = I# wild } in
--
-- Calls cmp and unboxes the Int result as I# y
--
case cmp @ a w w1 w2 w3 x x of _ { I# y ->
$s$wfoldlM'_loop (+# sc y) (+# sc1 1)
}
};
True -> sc
}; } in
$s$wfoldlM'_loop 0 0
}
-- helper function called by test - it calls $wa which calls boxed cmp
--
test1
:: forall a.
(Unbox a, Eq a) =>
Vector a -> Vector a -> Vector Int -> Id Int
test1 =
\ (@ a)
(w :: Unbox a)
(w1 :: Eq a)
(w2 :: Vector a)
(w3 :: Vector a)
(w4 :: Vector Int) ->
case $wa @ a w w1 w2 w3 w4 of ww { __DEFAULT ->
(I# ww) `cast` (Sym <(NTCo:Id <Int>)> :: Int ~# Id Int)
}
我将对如何强制从 test
调用 cmp
的未装箱版本的指针表示赞赏.我试图收紧不同的论点,但这就像把厨房水槽扔给它,这当然是行不通的.我希望可以利用此处获得的经验教训来解决更复杂的代码中的装箱/拆箱性能问题.
I will appreciate pointers on how to force unboxed version of cmp
to be called from test
. I tried strictifying different arguments, but that was like throwing the kitchen sink at it, which of course didn't work. I hope to use the lessons learnt here to solve the boxing/unboxing performance issue in the more complicated code.
另外,还有一个问题-我已经看到 cast
在核心中使用,但是在Haskell/GHC Wiki上找不到任何解释其含义的核心参考.似乎是类型转换操作.我希望能在上面的 test1
函数中解释它的含义以及如何解释它.
Also, one more question - I have seen cast
being used in the core, but haven't found any core references on Haskell/GHC wiki that explain what it is. It seems a type casting operation. I would appreciate explanation of what it is, and how to interpret it in the test1
function above.
推荐答案
现在我没有 ghc
,所以我的建议是口头的:
Now I don't have ghc
, so my advices would be verbal:
-
为什么要避免使用
{-#INLINE#-}
编译指示?Haskell的高性能很大程度上取决于函数内联.将INLINE
杂注添加到go
函数.
Why do you avoid
{-# INLINE #-}
pragma? High performance in Haskell is significantly based on function inlining. AddINLINE
pragma to thego
function.
删除 go
函数的前两个多余参数.在此处详细了解有关内联,专门化(拆箱)参数的互操作: http://www.haskell.org/ghc/docs/latest/html/users_guide/pragmas.html#inline-pragma
Remove first two excessive parameters of go
function. Read more about interoperation of inlining, specializing (unboxing) of parameters here: http://www.haskell.org/ghc/docs/latest/html/users_guide/pragmas.html#inline-pragma
将 m
和 n
定义与 go
一起上移一个级别.
Move m
and n
definitions one level up, along with go
.
这篇关于拆箱功能的文章就介绍到这了,希望我们推荐的答案对大家有所帮助,也希望大家多多支持!