18

私は最近、フリーFreeパッケージのモナドについて独学で学んでいますが、問題に遭遇しました。さまざまなライブラリにさまざまなフリーモナドを用意したいと考えています。基本的に、さまざまなコンテキストに対応する DSL を構築したいと考えていますが、それらを組み合わせることもできるようにしたいと考えています。例として:

{-# LANGUAGE DeriveFunctor #-}
module TestingFree where

import Control.Monad.Free

data BellsF x
    = Ring x
    | Chime x
    deriving (Functor, Show)

type Bells = Free BellsF

data WhistlesF x
    = PeaWhistle x
    | SteamWhistle x
    deriving (Functor, Show)

type Whistles = Free WhistlesF

ring :: Bells ()
ring = liftF $ Ring ()

chime :: Bells ()
chime = liftF $ Chime ()

peaWhistle :: Whistles ()
peaWhistle = liftF $ PeaWhistle ()

steamWhistle :: Whistles ()
steamWhistle = liftF $ SteamWhistle ()


playBells :: Bells r -> IO r
playBells (Pure r)         = return r
playBells (Free (Ring x))  = putStrLn "RingRing!" >> playBells x
playBells (Free (Chime x)) = putStr "Ding-dong!" >> playBells x

playWhistles :: Whistles () -> IO ()
playWhistles (Pure _)                = return ()
playWhistles (Free (PeaWhistle x))   = putStrLn "Preeeet!" >> playWhistles x
playWhistles (Free (SteamWhistle x)) = putStrLn "Choo-choo!" >> playWhistles x

今、私は両方のBellsAndWhistles機能を組み合わせることができるタイプを作成できるようにしたいと考えています。BellsWhistles

問題はモナドの結合にあるため、私が最初に考えたのはControl.Monad.Trans.Free、迅速かつ簡単な解決策を求めてモジュールを調べることでした。残念ながら、まばらな例があり、私がやりたいことを示すものはありません。また、2 つ以上のフリー モナドをスタックしMonadFreeても機能しないようですm -> f。基本的に、次のようなコードを記述できる機能が必要です。

newtype BellsAndWhistles m a = BellsAndWhistles
    { unBellsAndWhistles :: ???
    } deriving
        ( Functor
        , Monad
        -- Whatever else needed
        )

noisy :: Monad m => BellsAndWhistles m ()
noisy = do
    lift ring
    lift peaWhistle
    lift chime
    lift steamWhistle

play :: BellsAndWhistles IO () -> IO ()
play bellsNwhistles = undefined

しかし、別々のモジュールに存在することができ、お互いの実装について知る必要がないような方法Bellsで。Whistlesアイデアは、それぞれが独自の DSL を実装し、必要に応じてそれらを「より大きな」DSL に結合する方法を持つ、さまざまなタスク用のスタンドアロン モジュールを作成できるということです。これを行う簡単な方法はありますか?

play*おまけとして、既に記述されているさまざまな関数を活用して、それらを交換できるようになれば素晴らしいと思います。1 つの無料のインタープリターをデバッグ用に使用し、別のインタープリターを本番環境で使用できるようにしたいのですが、どの DSL を個別にデバッグするかを選択できると明らかに便利です。

4

2 に答える 2

29

これは、型クラスがない場合を除いて、紙のデータ型アラカルトに基づいた回答です。その論文を読むことをお勧めします。

Bellsトリックは、とのインタープリターを書く代わりに、次のようWhistlesに、単一のファンクター ステップと のインタープリターを定義することBellsFですWhistlesF

playBellsF :: BellsF (IO a) -> IO a
playBellsF (Ring  io) = putStrLn "RingRing!"  >> io
playBellsF (Chime io) = putStr   "Ding-dong!" >> io

playWhistlesF :: WhistelsF (IO a) -> IO a
playWhistlesF (PeaWhistle   io) = putStrLn "Preeeet!"   >> io
playWhistlesF (SteamWhistle io) = putStrLn "choo-choo!" >> io

それらを結合しないことを選択した場合は、それらを に渡すだけでControl.Monad.Free.iterM、元の play 関数を取り戻すことができます。

playBells    :: Bells a    -> IO a
playBells    = iterM playBell

playWhistles :: Whistles a -> IO a
playWhistles = iterM playWhistlesF

...ただし、単一のステップを扱うため、より簡単に組み合わせることができます。次のように、結合された新しい自由モナドを定義できます。

data BellsAndWhistlesF a = L (BellsF a) | R (WhistlesF a)

それを自由なモナドに変えます:

type BellsAndWhistles = Free BellsAndWhistlesF

次にBellsAndWhistlesF、2 つのサブインタープリターに関して、1 つのステップのインタープリターを作成します。

playBellsAndWhistlesF :: BellsAndWhistlesF (IO a) -> IO a
playBellsAndWhistlesF (L bs) = playBellsF    bs
playBellsAndWhistlesF (R ws) = playWhistlesF ws

...そして、それをに渡すだけで、フリーモナドのインタープリターを取得しますiterM:

playBellsAndWhistles :: BellsAndWhistles a -> IO a
playBellsAndWhistles = iterM playBellsAndWhistlesF

したがって、あなたの質問に対する答えは、フリー モナドを結合するための秘訣は、個々のファンクター ステップ (「代数」) の中間インタープリターを定義することによって、より多くの情報を保持することであるということです。これらの「代数」は、自由なモナドのインタプリタよりもはるかに結合しやすいです。

于 2014-01-28T02:20:07.020 に答える
18

ガブリエルの答えは的を射ていますが、すべてを機能させるもの、つまり2 つの s の合計FunctorFunctorも:

-- | Data type to encode the sum of two 'Functor's @f@ and @g@.
data Sum f g a = InL (f a) | InR (g a)

-- | The 'Sum' of two 'Functor's is also a 'Functor'.
instance (Functor f, Functor g) => Functor (Sum f g) where
    fmap f (InL fa) = InL (fmap f fa)
    fmap f (InR ga) = InR (fmap f ga)

-- | Elimination rule for the 'Sum' type.
elimSum :: (f a -> r) -> (g a -> r) -> Sum f g a -> r
elimSum f _ (InL fa) = f fa
elimSum _ g (InR ga) = g ga

(Edward Kmett のライブラリには、これがData.Functor.Coproduct.)

したがって、 s がモナドFunctorの「命令セット」である場合、次のようになります。Free

  1. Sum ファンクタは、そのような命令セットの和集合を提供し、したがって、対応する結合されたフリー モナドを提供します。
  2. 関数は、インタプリタ forとのインタプリタからインタプリタelimSumを構築できるようにする基本的なルールです。Sum f gfg

「データ型アラカルト手法は、この洞察を発展させたときに得られるものにすぎません。手作業でそれを解決するだけでも十分に価値があります。

この種のFunctor代数は、学ぶ価値のあるものです。例えば:

data Product f g a = Product (f a) (g a)

-- | The 'Product' of two 'Functor's is also a 'Functor'.
instance (Functor f, Functor g) => Functor (Product f g) where
   fmap f (Product fa ga) = Product (fmap f fa) (fmap f ga)

-- | The 'Product' of two 'Applicative's is also an 'Applicative'.
instance (Applicative f, Applicative g) => Applicative (Product f g) where
   pure x = Product (pure x) (pure x)
   Product ff gf <*> Product fa ga = Product (ff <*> fa) (gf <*> ga)


-- | 'Compose' is to 'Applicative' what monad transformers are to 'Monad'.
-- If your problem domain doesn't need the full power of the 'Monad' class, 
-- then applicative composition might be a good alternative on how to combine
-- effects.
data Compose f g a = Compose (f (g a))

-- | The composition of two 'Functor's is also a 'Functor'.
instance (Functor f, Functor g) => Functor (Compose f g) where
   fmap f (Compose fga) = Compose (fmap (fmap f) fga)

-- | The composition of two 'Applicative's is also an 'Applicative'.
instance (Applicative f, Applicative g) => Applicative (Compose f g) where
   pure = Compose . pure . pure
   Compose fgf <*> Compose fga = Compose ((<*>) <$> fgf <*> fga)

Gershom Bazerman のブログ エントリ"Abstracting with Applicatives"は、sに関するこれらの点を詳しく説明しApplicativeており、読む価値があります。


編集:最後に 1 つ注意しておきたいのは、人々Functorが free モナドの custom を設計するとき、実際には暗黙のうちにこれらの手法を正確に使用していることです。Gabriel の"Why free monads matter"から 2 つの例を取り上げます。

data Toy b next =
    Output b next
  | Bell next
  | Done

data Interaction next =
    Look Direction (Image -> next)
  | Fire Direction next
  | ReadLine (String -> next)
  | WriteLine String (Bool -> next)

Productこれらはすべて、 、SumCompose(->)ファンクターと次の 3 つの組み合わせに分析できます。

-- | Provided by "Control.Applicative"
newtype Const b a = Const b

instance Functor (Const b) where
    fmap _ (Const b) = Const b


-- | Provided by "Data.Functor.Identity"
newtype Identity a = Identity a

instance Functor Identity where
    fmap f (Identity a) = Identity (f a)


-- | Near-isomorphic to @Const ()@
data VoidF a = VoidF

instance Functor VoidF where
    fmap _ VoidF = VoidF

したがって、簡潔にするために次の型の同義語を使用します。

{-# LANGUAGE TypeOperators #-}

type f :+: g = Sum f g
type f :*: g = Product f g
type f :.: g = Compose f g

infixr 6 :+:
infixr 7 :*:
infixr 9 :.:

...これらのファンクターを次のように書き換えることができます。

type Toy b = Const b :*: Identity :+: Identity :+: VoidF

type Interaction = Const Direction :*: ((->) Image :.: Identity)
               :+: Const Direction :*: Identity
               :+: (->) String :.: Identity
               :+: Const String :*: ((->) Bool :.: Identity)
于 2014-01-28T02:37:30.147 に答える