2

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?

Cameron Ball
  • 4,048
  • 6
  • 25
  • 34
  • You could certainly change the implementation of `getInput` so that it modifies the state in some way after the `get`. But it would have to be in some determinate, fixed way. You can't make a program truly interactive without involving `IO`. – Robin Zigmond Sep 02 '19 at 07:09
  • Yeah, determinate and fixed way is what I am going for. Ideally I'd like to be able to run the program with a fixed set of inputs via `runState` and then when it needs to be interactive, just run it in the IO monad. – Cameron Ball Sep 02 '19 at 07:20
  • The similarities between the IO and State monads are striking. This allows to mimick and sequence user interactions in any language using pure functions. If you're curious about a JavaScript implementation, you can find it [here](https://faustinelli.wordpress.com/2014/06/01/state-monad-goes-to-js-town-and-starts-swinging/) – Marco Faustinelli Oct 14 '19 at 09:56

1 Answers1

3

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.

chi
  • 111,837
  • 3
  • 133
  • 218
  • I started playing around with this idea just as you suggested it! Thanks! – Cameron Ball Sep 02 '19 at 07:31
  • @CameronBall I changed it to use two lists, because it looks better to me. Otherwise, outputs are used for the next inputs, which feels wrong (IMO). – chi Sep 02 '19 at 07:33
  • Can you elaborate on the last edit a bit? It's not so clear how I would implement and run that. – Cameron Ball Sep 02 '19 at 07:47
  • @CameronBall I added a small real-IO interpreter. – chi Sep 02 '19 at 08:43
  • Cool! Getting off topic I guess... But I don't really get what writing interpreters gives me. In your example, if I wanted to run my IOpure without real IO, I would have to write something like `runIOpureState :: IOpure a -> State String a` - how is that better than having a typeclass which `State String` implements? – Cameron Ball Sep 03 '19 at 02:57
  • Further... writing the `Interaction` instances in terms of `IOpure` makes my `interactiveProgram` function not compile, since there's no monad instance for `IOpure`. But if the implementation is in the typeclass instance (rather than some `runIOpure` function), I get the monad instance for free for things like `IO` and `State`. I see a lot of people use this interpreter style though, so what am I missing that makes it so useful? – Cameron Ball Sep 03 '19 at 03:56
  • @CameronBall We can't use `State String` for that, since it models true interaction, where the user can see the outputs and provide inputs accordingly. There was a typo in the instance, which should have been for `IOpure` instead. There is no obvious way to write a truly general `runIOpure` I can see. I can give you one example of a less general one. – chi Sep 03 '19 at 07:42
  • I get that a specific implementation of `runIOpure` is require to run an `IOpure` in to a specific monad, that makes sense. What I don't understand is why it's good to put the implementation of that in to a specific `runIOpure` function vs just putting the implementation directly in the instance implementation. More precisely, why would I prefer to write a `runIOpure` function when I can just put the implementation directly in to the `IO` instance of `Interaction`? – Cameron Ball Sep 03 '19 at 08:30
  • @CameronBall An IO action can do anything, IOpure can only use the specific operations `Output` and `Input` -- no disk/network access, mutable variables, etc. But that's not necessarily "good". I only wanted to show another way to implement `Interaction`, without claiming it's better or worse. Ultimately, it depends on your goals. – chi Sep 03 '19 at 09:03
  • Makes sense! Thanks for the comprehensive answers :) – Cameron Ball Sep 06 '19 at 03:19