首页 > 解决方案 > 我可以使用 state monad 模拟交互式程序吗?

问题描述

基于此处的答案,我受到启发尝试制作一个程序,其中状态单子可以交换为 IO 单子,并且它仍然可以工作。到目前为止,我想出了:

{-# 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电话时,它会变得一团糟:

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

在 IO monad 的情况下,会提示用户输入另一个名称,并且输出类似于“Hey Jeff and Geoff”。但是在状态单子示例中,我无法提供第二个名称。相反,我得到((),"Hey Jeff and Jeff)了(提供的名称重复了两次)。

是否有可能为State String实例提出一个实现,允许任意多个“输入”被馈送到getInput调用中?

标签: haskelliostatemonads

解决方案


您可以改用两个字符串列表。一个用于输入,一个用于输出。

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会崩溃。

此外,这仅对启动时已知的输入进行建模。它不模拟可以相应地查看输出和答案的交互式用户。

最后,一个适当交互的程序可以用递归类型来建模

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 运行它,您可以使用

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价值的一种可能方式。

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 示例


推荐阅读