我可以使用状态monad模拟交互式程序吗? [英] Can I mock an interactive program using the state monad?

查看:116
本文介绍了我可以使用状态monad模拟交互式程序吗?的处理方法,对大家解决问题具有一定的参考价值,需要的朋友们下面随着小编来一起学习吧!

问题描述

基于此处的答案,我受到启发,尝试创建一个程序,在该程序中可以将状态monad替换为IO monad,它将仍然有效.到目前为止,我想到了:

Based on an answer here I was inspired to try and make a program where the state monad could be swapped for the IO monad and it would still work. So far I came up with:

{-# LANGUAGE FlexibleInstances #-}

import Control.Monad.State

class Monad m => Interaction m where
  getInput :: m String
  produceOutput :: String -> m ()

instance Interaction IO where
  getInput = getLine
  produceOutput = putStrLn

instance Interaction (State String) where
  getInput = get
  produceOutput = put

interactiveProgram :: Interaction m => m ()
interactiveProgram = do
  name <- getInput
  produceOutput $ "Hey " ++ name

如果我在GHCi中运行它,则可以很好地运行,而且还可以像这样运行interactiveProgram:runState interactiveProgram "Jeff".但是,当我添加额外的getInput调用时,它会变得混乱:

This works fine if I run it in GHCi, and I can also run interactiveProgram like so: runState interactiveProgram "Jeff". It gets messy when I add extra getInput calls though:

interactiveProgram :: Interaction m => m ()
interactiveProgram = do
  name <- getInput
  name2 <- getInput
  produceOutput $ "Hey " ++ name ++ " and " ++ name2

在IO monad的情况下,系统会提示用户输入其他名称,并且输出类似"Hey Jeff and Geoff".但是在状态monad的示例中,我无法提供第二个名字.相反,我得到((),"Hey Jeff and Jeff)(提供的名称重复两次).

In the case of the IO monad, the user is prompted for another name and the output is something like "Hey Jeff and Geoff". But in the state monad example, I have no way to provide that second name. Instead I get ((),"Hey Jeff and Jeff) (the provided name repeated twice).

是否可以为State String实例提出一个实现,该实现允许任意多个输入"馈入getInput调用?

Is it possible to come up with an implementation for the State String instance that allows arbitrarily many "inputs" that get fed to the getInput calls?

推荐答案

您可以改为使用两个字符串列表.一种用于输入,一种用于输出.

You could use two lists of strings instead. One for the inputs, one for the outputs.

instance Interaction (State ([String],[String])) where
  getInput = do
     (x:xs,o) <- get
     put (xs,o)
     return x
  produceOutput x = do
     (i,o) <- get
     put (i,x:o)

这假定初始状态包含足够大的输入字符串列表.太短了,getInput会崩溃.

This assumes that the initial state contains a large enough list of input strings. It that's too short, getInput will crash.

此外,这仅对启动时已知的输入进行建模.它不会为可以看到输出并做出相应回答的交互式用户建模.

Further, this only models inputs which are known at startup. It does not model an interactive user who can see the outputs and answers accordingly.

最后,可以通过递归类型对适当的交互程序进行建模

Finally, a properly interactive program can be modeled by the recursive type

data IOpure a 
  = Return a
  | Output String (IOpure a)
  | Input (String -> IOpure a)
  deriving Functor

instance Applicative IOpure where
   pure = Return
   (<*>) = ap

instance Monad IOpure where
   Return x >>= f = f x
   Output s io >>= f = Output s (io >>= f)
   Input k >>= f = Input (\s -> k s >>= f)

instance Interaction IOpure where
  getInput = Input Return
  produceOutput x = Output x (Return ())

要使用实际的IO运行此命令,您可以使用

To run this using actual IO, you can use

runIOpure :: IOpure a -> IO a
runIOpure (Return x)    = return x
runIOpure (Output x io) = putStrLn x >> runIOpure io
runIOpure (Input k)     = getLine >>= runIOpure . k

另一个示例:这为用户建模,当提示输入时,该用户回显最后一个输出(或在开始时无输出").这只是消耗IOpure a值的一种可能方式.

Another example: this models a user which, when prompted for an input, echoes the last output (or "no output", at the very beginning). This is just one possible way of consuming an IOpure a value.

echoingUser :: IOpure a -> a
echoingUser = go "no output"
   where
   go _ (Return x)    = x
   go _ (Output o io) = go o io
   go o (Input k)     = go o (k o)

您可以尝试在

上使用echoingUser

interactiveProgram :: Interaction m => m (String, String)
interactiveProgram = do
  produceOutput "Jeff"
  name <- getInput
  produceOutput "Bob"
  name2 <- getInput
  return (name, name2)

尝试使用上述所有代码的 ideone示例.

Try the ideone example with all the code above.

这篇关于我可以使用状态monad模拟交互式程序吗?的文章就介绍到这了,希望我们推荐的答案对大家有所帮助,也希望大家多多支持IT屋!

查看全文
登录 关闭
扫码关注1秒登录
发送“验证码”获取 | 15天全站免登陆