2013-09-03 3 views
30

一部のパーサーのApplicativeインタフェースは、Monadインタフェースよりも効率的に実装されていると聞きました。その理由は、Applicativeでは、有効な計算がすべて実行される前に、すべての「効果」を事前に知っているからです。モナドでは、効果は計算中の値に依存することがあります。したがって、この最適化は不可能です。Monadの部分よりも応用部分の方が最適化されたモナドの例

私はこれの良い例を見たいと思います。それは、非常に単純なパーサまたはいくつかの異なるモナドであり、重要ではありません。重要なことは、そのようなモナドのApplicativeインターフェイスがreturnapに準拠していますが、Applicativeを使用すると、より効率的なコードが生成されることです。

更新:ここでは明確にするために、私はモナドには適用できないアプリケーションには興味がありません。問題は、両方のことです。

+7

facebookで[The Haxl project](https://github.com/meiersi/HaskellerZ/blob/master/meetups/20130829-FPAfternoon_The_Haxl_Project_at_Facebook/The%20Haxl%20Project%20at%20Facebook.pdf?raw=true)でインタレースされました。計算を並列化することができるアプリケーションを使用します。モナドインターフェースを使用して計算を並列化することはできません。 – bennofs

答えて

19

もう1つの例は、厳密な左折です。折りたたみを作成して折り畳みを1回のパスと一定の間隔でデータ上で実行できるようにするアプリケーションインスタンスを作成することができます。しかし、モナドのインスタンスは各バインドのデータの先頭から再イテレートし、リスト全体をメモリ内に保持する必要があります。

{-# LANGUAGE GADTs #-} 

import Criterion.Main 

import Data.Monoid 
import Control.Applicative 
import Control.Monad 

import Prelude hiding (sum) 

data Fold e r where 
    Step :: !(a -> e -> a) -> !a -> !(a -> r) -> Fold e r 
    Bind :: !(Fold e r) -> !(r -> Fold e s) -> Fold e s 

data P a b = P !a !b 

instance Functor (Fold e) where 
    fmap f (Step step acc ret) = Step step acc (f . ret) 
    fmap f (Bind fld g) = Bind fld (fmap f . g) 

instance Applicative (Fold e) where 
    pure a = Step const a id 
    Step fstep facc fret <*> Step xstep xacc xret = Step step acc ret where 
     step (P fa xa) e = P (fstep fa e) (xstep xa e) 
     acc = P facc xacc 
     ret (P fa xa) = (fret fa) (xret xa) 

    Bind fld g <*> fldx = Bind fld ((<*> fldx) . g) 
    fldf <*> Bind fld g = Bind fld ((fldf <*>) . g) 

instance Monad (Fold e) where 
    return = pure 
    (>>=) = Bind 

fold :: Fold e r -> [e] -> r 
fold (Step _ acc ret) [] = ret acc 
fold (Step step acc ret) (x:xs) = fold (Step step (step acc x) ret) xs 
fold (Bind fld g) lst = fold (g $ fold fld lst) lst 

monoidalFold :: Monoid m => (e -> m) -> (m -> r) -> Fold e r 
monoidalFold f g = Step (\a -> mappend a . f) mempty g 

count :: Num n => Fold e n 
count = monoidalFold (const (Sum 1)) getSum 

sum :: Num n => Fold n n 
sum = monoidalFold Sum getSum 

avgA :: Fold Double Double 
avgA = liftA2 (/) sum count 

avgM :: Fold Double Double 
avgM = liftM2 (/) sum count 

main :: IO() 
main = defaultMain 
    [ bench "Monadic"  $ nf (test avgM) 1000000 
    , bench "Applicative" $ nf (test avgA) 1000000 
    ] where test f n = fold f [1..n] 

私はそれが応用的とモナド折り目に最適な実装ではないかもしれませんので、一例として、私の頭の上から上記を書いたが、上記実行すると、私を与える:

あなたがかもしれない
benchmarking Monadic 
mean: 119.3114 ms, lb 118.8383 ms, ub 120.2822 ms, ci 0.950 
std dev: 3.339376 ms, lb 2.012613 ms, ub 6.215090 ms, ci 0.950 

benchmarking Applicative 
mean: 51.95634 ms, lb 51.81261 ms, ub 52.15113 ms, ci 0.950 
std dev: 850.1623 us, lb 667.6838 us, ub 1.127035 ms, ci 0.950 
+0

[foldlパッケージ](http://hackage.haskell.org/package/foldl)は基本的にこのアイデアの精緻化です。 – sjakobi

17

多分、標準的な例はベクトルによって与えられます。

data Nat = Z | S Nat deriving (Show, Eq, Ord) 

data Vec :: Nat -> * -> * where 
    V0 ::     Vec Z x 
    (:>) :: x -> Vec n x -> Vec (S n) x 

まず、シングルトンを定義してクラスにラップすることで、少しの努力でそれを適用することができます。

data Natty :: Nat -> * where 
    Zy :: Natty Z 
    Sy :: Natty n -> Natty (S n) 

class NATTY (n :: Nat) where 
    natty :: Natty n 

instance NATTY Z where 
    natty = Zy 

instance NATTY n => NATTY (S n) where 
    natty = Sy natty 

今度は私は(TraversableインスタンスからfmapDefaultを介して抽出されるべきである)Functorインスタンスを省略Applicative構造

instance NATTY n => Applicative (Vec n) where 
    pure = vcopies natty 
    (<*>) = vapp 

vcopies :: forall n x. Natty n -> x -> Vec n x 
vcopies Zy  x = V0 
vcopies (Sy n) x = x :> vcopies n x 

vapp :: forall n s t. Vec n (s -> t) -> Vec n s -> Vec n t 
vapp V0   V0   = V0 
vapp (f :> fs) (s :> ss) = f s :> vapp fs ss 

を開発することができます。

今、Applicativeに対応するMonadインスタンスがありますが、それは何ですか? 対角線思考!それが必要なのです!ベクトルは有限領域からの関数の表として見ることができるので、ApplicativeはK-およびS-コンビネータの単なる表であり、MonadReaderのような振る舞いを持っています。

vtail :: forall n x. Vec (S n) x -> Vec n x 
vtail (x :> xs) = xs 

vjoin :: forall n x. Natty n -> Vec n (Vec n x) -> Vec n x 
vjoin Zy  _     = V0 
vjoin (Sy n) ((x :> _) :> xxss) = x :> vjoin n (fmap vtail xxss) 

instance NATTY n => Monad (Vec n) where 
    return = vcopies natty 
    xs >>= f = vjoin natty (fmap f xs) 

あなたはより直接的>>=を定義することによって、ビットを節約するかもしれませんが、あなたはそれをカットどのような方法は、モナド行動は非対角計算のための役に立たないサンクを作成します。怠惰は、アーケードドン要因によって減速するのを防ぐかもしれませんが、<*>のジッパー動作は、少なくとも行列の対角を取るよりも少し安いことになります。

14

pigworkerによると、配列は明らかな例です。そのモナドインスタンス等型インデックス長の概念レベルでほんの少し問題ではなく、また、非常に現実世俗的Data.Vector実装で悪化行う:

import Criterion.Main 
import Data.Vector as V 

import Control.Monad 
import Control.Applicative 

functions :: V.Vector (Int -> Int) 
functions = V.fromList [(+1), (*2), (subtract 1), \x -> x*x] 

values :: V.Vector Int 
values = V.enumFromN 1 32 

type NRuns = Int 

apBencher :: (V.Vector (Int -> Int) -> V.Vector Int -> V.Vector Int) 
      -> NRuns -> Int 
apBencher ap' = run values 
where run arr 0 = V.sum arr 
     run arr n = run (functions `ap'` arr) $ n-1 

main = defaultMain 
     [ bench "Monadic"  $ nf (apBencher ap ) 4 
     , bench "Applicative" $ nf (apBencher (<*>)) 4 ] 

$ GHC-7.6 - O1 -o -fllvm -oビン/ベンチ-D0 def0.hs
$ベンチ-D0
クロックの分解能を推定
をウォーミングアップ...
意味1.516271である私たち(640001回のイテレーション)
639999の間で3768外れ値を発見しましたサンプル(0.6%)2924(0。12個のサンプル(8.3%)
1(8.3%)、重度

高いうち1外れ値を発見したクロック・コールのコストを推定5%)高い重症
...
意味は41.62906 NS(12回の反復)
あります ベンチマーク単項
平均:UB 2.769786ミリ、2.779151ミリ、CI 0.950
のstd devのポンド2.773062ミリ秒、:22.14540たち、13.55686ポンドたち、UB 36.88265たち、0.950

CIベンチマーク平均
のApplicative:1。 CI UB 1.267654ミリ、1.271526ミリポンド269351ミリ秒、0.950
のSTD DEV:9.799454たち、私たち8.171284ポンド、UB 13.09267たち、それはパフォーマンスの差で出てこないことCI 0.950

注意-O2でコンパイルすると明らかにap<*>に置き換えられます。しかし、>>=は、各関数呼び出しの後に適切な量のメモリを割り当ててから、結果を整えることができます。これはかなり時間がかかるようです。 <*>は、結果の長さをfunctionsvaluesの積として単純に計算してから、1つの固定配列に書き込むことができます。

関連する問題