9

I am trying to abstract the pattern of applying a certain semantics to a free monad over some functor. The running example I am using to motivate this is applying updates to an entity in a game. So I import a few libraries and define a few example types and an entity class for the purposes of this example (I am using the free monad implementation in control-monad-free):

{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE TypeFamilies #-}

import Control.Monad.Free
import Control.Monad.Identity
import Control.Monad.Writer

-- Things which can happen to an entity
data Order = Order deriving Show
data Damage = Damage deriving Show

class Entity a where
    evolve :: Double -> a -> a
    order :: Order -> a -> a
    damage :: Damage -> a -> a

-- Make a trivial entity for testing purposes
data Example = Example deriving Show
instance Entity Example where
    evolve _ a = a
    order _ a = a
    damage _ a = a

-- A type to hold all the possible update types
data EntityUpdate = 
      UpdateTime Double
    | UpdateOrder Order
    | UpdateDamage Damage
    deriving (Show)

-- Wrap UpdateMessage to create a Functor for constructing the free monad
data UpdateFunctor cont = 
    UpdateFunctor {updateMessage :: EntityUpdate, continue :: cont} deriving (Show, Functor)

-- Type synonym for the free monad
type Update = Free UpdateEntity

I now lift some basic updates into the monad:

liftF = wrap . fmap Pure

updateTime :: Double -> Update ()
updateTime t = liftUpdate $ UpdateTime t

updateOrder :: Order -> Update ()
updateOrder o = liftUpdate $ UpdateOrder o

updateDamage :: Damage -> Update ()
updateDamage d = liftUpdate $ UpdateDamage d

test :: Update ()
test = do
    updateTime 8.0
    updateOrder Order
    updateDamage Damage
    updateTime 4.0
    updateDamage Damage
    updateTime 6.0
    updateOrder Order
    updateTime 8.0

Now we have the free monad, we need to provide the possibility of different implementations, or semantic interpretations, of monad instance such as test above. The best pattern I can come up with for this is given by the following function:

interpret :: (Monad m, Functor f, fm ~ Free f c) => (f fm -> fm) -> (f fm -> a -> m a) -> fm -> a -> m a
interpret _ _ (Pure _  ) entity = return entity
interpret c f (Impure u) entity = f u entity >>= interpret c f (c u)

Then with some basic semantic functions we can give the two following possible interpretations, one as a basic evaluation and one as a writer monad preforming logging:

update (UpdateTime t) = evolve t
update (UpdateOrder o) = order o
update (UpdateDamage d) = damage d

eval :: Entity a => Update () -> a -> a
eval updates entity = runIdentity $ interpret continue update' updates entity where
    update' u entity = return $ update (updateMessage u) entity

logMessage (UpdateTime t) = "Simulating time for " ++ show t ++ " seconds.\n"
logMessage (UpdateOrder o) = "Giving an order.\n"
logMessage (UpdateDamage d) = "Applying damage.\n"

evalLog :: Entity a => Update () -> a -> Writer String a
evalLog = interpret continue $ \u entity -> do
    let m = updateMessage u
    tell $ logMessage m
    return $ update m entity

Testing this in GHCI:

> eval test Example
Example
> putStr . execWriter $ evalLog test Example
Simulating time for 8.0 seconds.
Giving an order.
Applying damage.
Simulating time for 4.0 seconds.
Applying damage.
Simulating time for 6.0 seconds.
Giving an order.
Simulating time for 8.0 seconds.

This all works fine, but it gives me a slightly uneasy feeling that it could be more general, or could be better organised. Having to provide a function to provide the continuation wasn't obvious at first and I'm not sure it is the best approach. I have made several efforts to redefine interpret in terms of functions in the Control.Monad.Free module, such as foldFree and induce. But they all seem to not quite work.

Am I on the right lines with this, or am a making a misjudgement? Most of the articles on free monads I have found concentrate on their efficiency or different ways to implement them, rather than on patterns for actually using them like this.

It also seems desirable to encapsulate this in some kind of Semantic class, so I could simply make different monad instances from my free monad by wrapping the functor in a newtype and making it an instance of this class. I couldn't quite work out how to do this however.

UPDATE --

I wish I could have accepted both answers as they are both extremely informative and thoughtfully written. In the end though, the edit to the accepted answer contains the function I was after:

interpret :: (Functor m, Monad m) => (forall x. f x -> m x) -> Free f a -> m a
interpret evalF = retract . hoistFree evalF

(retract and hoistFree are in Edward Kemmet's free package in Control.Monad.Free).

All three of pipes, operational and sacundim's free-operational package are very relevant and look like they will be very useful for me in the future. Thank you all.

4

2 回答 2

7

你可以使用我的pipes库,它为使用免费的 monad 提供了更高级别的抽象。

pipes使用自由单子来具体化计算的每个部分:

  • 数据(即您的Producer更新)是一个免费的单子
  • 数据(即你的Consumer解释器)是一个免费的单子
  • 数据(即您的Pipe记录器)是一个免费的单子

事实上,它们并不是三个独立的自由单子:它们都是伪装的自由单子。一旦定义了这三个,就可以使用管道组合将它们连接起来(>->),以便开始流式传输数据。

我将从您的示例的略微修改版本开始,该版本跳过您编写的类型类:

{-# LANGUAGE RankNTypes #-}

import Control.Lens
import Control.Proxy
import Control.Proxy.Trans.State
import Control.Monad.Trans.Writer

data Order  = Order deriving (Show)
data Damage = Damage deriving (Show)

data EntityUpdate
    = UpdateTime   Double
    | UpdateOrder  Order
    | UpdateDamage Damage
    deriving (Show)

现在我们要做的是定义UpdateaProducerEntityUpdates 的 a:

type Update r = forall m p . (Monad m, Proxy p) => Producer p EntityUpdate m r

然后我们定义实际的命令。每个命令使用管道原语产生相应的更新respond,将数据进一步发送到下游进行处理。

updateTime :: Double -> Update ()
updateTime t = respond (UpdateTime t)

updateOrder :: Order -> Update ()
updateOrder o = respond (UpdateOrder o)

updateDamage :: Damage -> Update ()
updateDamage d = respond (UpdateDamage d)

由于 aProducer是一个自由单子,我们可以使用do符号来组装它,就像你为你的test函数所做的那样:

test :: () -> Update ()
-- i.e. () -> Producer p EntityUpdate m ()
test () = runIdentityP $ do
    updateTime 8.0
    updateOrder Order
    updateDamage Damage
    updateTime 4.0
    updateDamage Damage
    updateTime 6.0
    updateOrder Order
    updateTime 8.0

但是,我们也可以将解释器具体化为Consumer数据。这很好,因为我们可以直接在解释器上对状态进行分层,而不是使用Entity您定义的类。

我将使用一个简单的状态:

data MyState = MyState { _numOrders :: Int, _time :: Double, _health :: Int }
    deriving (Show)

begin :: MyState
begin= MyState 0 0 100

...并为清晰起见定义了一些方便的镜头:

numOrders :: Lens' MyState Int
numOrders = lens _numOrders (\s x -> s { _numOrders = x})

time :: Lens' MyState Double
time = lens _time (\s x -> s { _time = x })

health :: Lens' MyState Int
health = lens _health (\s x -> s { _health = x })

...现在我可以定义一个有状态的解释器:

eval :: (Proxy p) => () -> Consumer (StateP MyState p) EntityUpdate IO r
eval () = forever $ do
    entityUpdate <- request ()
    case entityUpdate of
        UpdateTime   tDiff -> modify (time      +~ tDiff)
        UpdateOrder  _     -> modify (numOrders +~ 1    )
        UpdateDamage _     -> modify (health    -~ 1    )
    s <- get
    lift $ putStrLn $ "Current state is: " ++ show s

这使得解释器在做什么变得更加清楚。我们可以一目了然地看到它如何以有状态的方式处理传入的值。

为了连接我们的ProducerConsumer我们使用(>->)组合运算符,然后是runProxy,它将我们的管道转换回基本 monad:

main1 = runProxy $ evalStateK begin $ test >-> eval

...产生以下结果:

>>> main1
Current state is: MyState {_numOrders = 0, _time = 8.0, _health = 100}
Current state is: MyState {_numOrders = 1, _time = 8.0, _health = 100}
Current state is: MyState {_numOrders = 1, _time = 8.0, _health = 99}
Current state is: MyState {_numOrders = 1, _time = 12.0, _health = 99}
Current state is: MyState {_numOrders = 1, _time = 12.0, _health = 98}
Current state is: MyState {_numOrders = 1, _time = 18.0, _health = 98}
Current state is: MyState {_numOrders = 2, _time = 18.0, _health = 98}
Current state is: MyState {_numOrders = 2, _time = 26.0, _health = 98}

您可能想知道为什么我们必须分两步执行此操作。为什么不直接去掉runProxy部分?

原因是我们可能希望组合两个以上的东西。例如,我们可以很容易地在test和之间插入一个日志记录阶段eval。我称这些中间阶段Pipe为:

logger
    :: (Monad m, Proxy p)
    => () -> Pipe p EntityUpdate EntityUpdate (WriterT String m) r
logger () = runIdentityP $ forever $ do
    entityUpdate <- request ()
    lift $ tell $ case entityUpdate of
        UpdateTime   t -> "Simulating time for " ++ show t ++ " seconds.\n"
        UpdateOrder  o -> "Giving an order.\n"
        UpdateDamage d -> "Applying damage.\n"
    respond entityUpdate

同样,我们可以非常清楚地看到是做什么logger的:它request是值,是值tell的表示形式,然后使用 . 将值进一步传递到下游respond

我们可以在test和之间插入它logger。我们唯一必须注意的是所有阶段都必须具有相同的基本 monad,因此我们使用raiseK插入一个WriterT层,eval以便它与 的基本 monad 匹配logger

main2 = execWriterT $ runProxy $ evalStateK begin $
    test >-> logger >-> raiseK eval

...产生以下结果:

>>> main2
Current state is: MyState {_numOrders = 0, _time = 8.0, _health = 100}
Current state is: MyState {_numOrders = 1, _time = 8.0, _health = 100}
Current state is: MyState {_numOrders = 1, _time = 8.0, _health = 99}
Current state is: MyState {_numOrders = 1, _time = 12.0, _health = 99}
Current state is: MyState {_numOrders = 1, _time = 12.0, _health = 98}
Current state is: MyState {_numOrders = 1, _time = 18.0, _health = 98}
Current state is: MyState {_numOrders = 2, _time = 18.0, _health = 98}
Current state is: MyState {_numOrders = 2, _time = 26.0, _health = 98}
"Simulating time for 8.0 seconds.\nGiving an order.\nApplying damage.\nSimulating time for 4.0 seconds.\nApplying damage.\nSimulating time for 6.0 seconds.\nGiving an order.\nSimulating time for 8.0 seconds.\n"

pipes旨在解决您描述的那种问题。很多时候,我们不仅想具体化生成数据的 DSL,还想具体化解释器和中间处理阶段。 pipes同等对待所有这些概念,并将它们全部建模为可连接的流 DSL。这使得交换各种行为变得非常容易,而无需定义自己的自定义解释器框架。

如果您不熟悉管道,那么您可能需要查看教程

于 2013-04-10T18:41:21.143 回答
3

我不太明白你的例子,但我认为你基本上是operational在这里重建包。您的EntityUpdate类型非常像 意义上的指令集operational,而您的类型就像指令集上UpdateFunctor的自由函子——这正是关联operational和自由单子的构造。(请参阅“操作真的与自由单子同构吗?”这个 Reddit 讨论)。

但无论如何,这个operational包有你想要的功能,interpretWithMonad

interpretWithMonad :: forall instr m b.
                      Monad m => 
                      (forall a. instr a -> m a) 
                   -> Program instr b
                   -> m b

这允许您提供一个函数,将程序中的每个指令(每个EntityUpdate值)解释为一个单子操作,并处理其余部分。

如果允许我进行一点自我推销,我最近正在编写自己的operational使用免费 monads的版本,因为我想要一个's类型的Applicative版本。因为你的例子让我觉得纯粹是应用性的,所以我根据我的库进行了编写你的练习,我不妨把它粘贴在这里。(我无法理解你的功能。)这里是:operationalProgramevalLogeval

{-# LANGUAGE GADTs, ScopedTypeVariables, RankNTypes #-}

import Control.Applicative
import Control.Applicative.Operational
import Control.Monad.Writer

data Order = Order deriving Show
data Damage = Damage deriving Show

-- UpdateI is short for "UpdateInstruction"
data UpdateI a where
    UpdateTime   :: Double -> UpdateI ()
    UpdateOrder  :: Order -> UpdateI ()
    UpdateDamage :: Damage -> UpdateI ()

type Update = ProgramA UpdateI

updateTime :: Double -> Update ()
updateTime = singleton . UpdateTime

updateOrder :: Order -> Update ()
updateOrder = singleton . UpdateOrder

updateDamage :: Damage -> Update ()
updateDamage = singleton . UpdateDamage

test :: Update ()
test = updateTime 8.0 
    *> updateOrder Order
    *> updateDamage Damage
    *> updateTime 4.0
    *> updateDamage Damage
    *> updateTime 6.0
    *> updateOrder Order
    *> updateTime 8.0

evalLog :: forall a. Update a -> Writer String a
evalLog = interpretA evalI
    where evalI :: forall x. UpdateI x -> Writer String x
          evalI (UpdateTime t) = 
              tell $ "Simulating time for " ++ show t ++ " seconds.\n"
          evalI (UpdateOrder Order) = tell $ "Giving an order.\n"
          evalI (UpdateDamage Damage) = tell $ "Applying damage.\n"

输出:

*Main> putStr $ execWriter (evalLog test)
Simulating time for 8.0 seconds.
Giving an order.
Applying damage.
Simulating time for 4.0 seconds.
Applying damage.
Simulating time for 6.0 seconds.
Giving an order.
Simulating time for 8.0 seconds.

interpretWithMonad这里的技巧与原始包中的函数相同,但适用于应用程序:

interpretA :: forall instr f a. Applicative f =>
              (forall x. instr x -> f x)
           -> ProgramA instr a -> f a

如果您真的需要一元解释,则只需导入Control.Monad.Operational(原始的或我的)代替Control.Applicative.Operational,并使用Program代替ProgramA. ProgramA但是,您可以更强大地静态检查程序:

-- Sum the total time requested by updateTime instructions in an
-- applicative UpdateI program.  You can't do this with monads.
sumTime :: ProgramA UpdateI () -> Double
sumTime = sumTime' . viewA 
    where sumTime' :: forall x. ProgramViewA UpdateI x -> Double
          sumTime' (UpdateTime t :<**> k) = t + sumTime' k
          sumTime' (_ :<**> k) = sumTime' k
          sumTime' (Pure _) = 0

的示例用法sumTime

*Main> sumTime test
26.0

编辑:回想起来,我应该提供这个较短的答案。这假设您使用Control.Monad.Free的是 Edward Kmett 的软件包:

interpret :: (Functor m, Monad m) =>
             (forall x. f x -> m x) 
          -> Free f a -> m a
interpret evalF = retract . hoistFree evalF
于 2013-04-11T08:37:12.020 回答