什么是惹巴2和3层的API之间的主要区别?(What are the key differences

2019-06-24 19:18发布

更具体地讲,我有以下看似平淡无奇的小惹巴3的程序:

{-# LANGUAGE QuasiQuotes #-}

import Prelude hiding (map, zipWith)
import System.Environment (getArgs)
import Data.Word (Word8)
import Data.Array.Repa
import Data.Array.Repa.IO.DevIL
import Data.Array.Repa.Stencil
import Data.Array.Repa.Stencil.Dim2

main = do
  [s] <- getArgs
  img <- runIL $ readImage s

  let out = output x where RGB x = img
  runIL . writeImage "out.bmp" . Grey =<< computeP out

output img = map cast . blur . blur $ blur grey
  where
    grey              = traverse img to2D luminance
    cast n            = floor n :: Word8
    to2D (Z:.i:.j:._) = Z:.i:.j

---------------------------------------------------------------

luminance f (Z:.i:.j)   = 0.21*r + 0.71*g + 0.07*b :: Float
  where
    (r,g,b) = rgb (fromIntegral . f) i j

blur = map (/ 9) . convolve kernel
  where
    kernel = [stencil2| 1 1 1
                        1 1 1
                        1 1 1 |]

convolve = mapStencil2 BoundClamp

rgb f i j = (r,g,b)
  where
    r = f $ Z:.i:.j:.0
    g = f $ Z:.i:.j:.1
    b = f $ Z:.i:.j:.2

这需要这么多的时间来对我的2GHz的Core 2 Duo处理器的笔记本电脑处理640x420的图像:

real    2m32.572s
user    4m57.324s
sys     0m1.870s

我知道的东西一定是十分错误的,因为我已经得到了使用惹巴2.根据该API更复杂的算法更好的性能,大大的提高了,我发现从加入呼叫“力”来每个数组转换之前(我的理解意味着每次调用地图,卷积,移等)。 我不能完全辨认出类似的事情惹巴3做 - 其实我认为新的表现类型参数都应该保证没有关于当阵列需要被强制歧义? 以及如何在新的一元界面融入这个计划? 我看过唐S中的不错的教程,但也有惹巴2和3层的API被讨论了一点网上AFAIK之间的一些关键差距。

更简单地说,有没有解决上述程序的效率,最低限度影响力呢?

Answer 1:

新表示类型的参数需要时不自动的力(它可能是一个困难的问题做的那么好) - 你还是要手动强制。 在惹巴3,这是与computeP函数来完成:

computeP
  :: (Monad m, Repr r2 e, Fill r1 r2 sh e)
  => Array r1 sh e -> m (Array r2 sh e)

我个人真的不明白为什么它的单子,因为你可以一样好使用Monad的身份:

import Control.Monad.Identity (runIdentity)
force
  :: (Repr r2 e, Fill r1 r2 sh e)
  => Array r1 sh e -> Array r2 sh e
force = runIdentity . computeP

所以,现在你的output功能,可以用适当的强制改写:

output img = map cast . f . blur . f . blur . f . blur . f $ grey
  where ...

利用缩写f使用辅助功能u帮助类型推断:

u :: Array U sh e -> Array U sh e
u = id
f = u . force

这些变化,加速是相当显着 - 这是可以预料的,因为没有中间施力每个输出像素结束了评估远远超过是必要的(在中间的值不被共享)。

你原来的代码:

real    0m25.339s
user    1m35.354s
sys     0m1.760s

随着迫使:

real    0m0.130s
user    0m0.320s
sys     0m0.028s

具有600x400 PNG经测试,输出文件是相同的。



Answer 2:

computeP is the new force.

In Repa 3 you need to use computeP everywhere you would have used force in Repa 2.

The Laplace example from repa-examples is similar to what you're doing. You should also use cmap instead of plain map in your blur function. There will be a paper explaining why on my homepage early next week.



文章来源: What are the key differences between the Repa 2 and 3 APIs?