Can I mock an interactive program using the state monad?

时光毁灭记忆、已成空白 提交于 2020-01-02 10:18:35

问题


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

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

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).

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?


回答1:


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)

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 ())

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

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)

You could try using echoingUser on

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

Try the ideone example with all the code above.



来源:https://stackoverflow.com/questions/57752413/can-i-mock-an-interactive-program-using-the-state-monad

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!