问题
Being quite new to Haskell, I'm currently trying to improve my skills by writing an interpreter for a simple imperative toy language.
One of the expressions in this language is input
, which reads a single integer from standard input. However, when I assign the value of this expression to a variable and then use this variable later, it seems ot me that I actually stored the computation of reading a value rather the read value itself. This means that e.g. the statements
x = input;
y = x + x;
will cause the interpreter to invoke the input procedure three times rather than one.
Internally in the evaluator module, I use a Map
to store the values of variables. Because I need to deal with IO, this gets wrapped in an IO
monad, as immortalized in the following minimal example:
import qualified Data.Map as Map
type State = Map.Map String Int
type Op = Int -> Int -> Int
input :: String -> IO State -> IO State
input x state = do line <- getLine
st <- state
return $ Map.insert x (read line) st
get :: String -> IO State -> IO Int
get x state = do st <- state
return $ case Map.lookup x st of
Just i -> i
eval :: String -> Op -> String -> IO State -> IO Int
eval l op r state = do i <- get l state
j <- get r state
return $ op i j
main :: IO ()
main = do let state = return Map.empty
let state' = input "x" state
val <- eval "x" (+) "x" state'
putStrLn . show $ val
The second line in the main
function simulates the assignment of x
, while the third line simulates the evaluation of the binary +
operator.
My question is: How do I get around this, such that the code above only inputs once? I suspect that it is the IO
-wrapping that causes the problem, but as we're dealing with IO I see no way out of that..?
回答1:
Remember that IO State
is not an actual state, but instead the specification for an IO
machine which eventually produces a State
. Let's consider input
as an IO
-machine transformer
input :: String -> IO State -> IO State
input x state = do line <- getLine
st <- state
return $ Map.insert x (read line) st
Here, provided a machine for producing a state, we create a bigger machine which takes that passed state and adding a read
from an input line. Again, to be clear, input name st
is an IO
-machine which is a slight modification of the IO
-machine st
.
Let's now examine get
get :: String -> IO State -> IO Int
get x state = do st <- state
return $ case Map.lookup x st of
Just i -> i
Here we have another IO
-machine transformer. Given a name and an IO
-machine which produces a State
, get
will produce an IO
-machine which returns a number. Note again that get name st
is fixed to always use the state produced by the (fixed, input) IO
-machine st
.
Let's combine these pieces in eval
eval :: String -> Op -> String -> IO State -> IO Int
eval l op r state = do i <- get l state
j <- get r state
return $ op i j
Here we call get l
and get r
each on the same IO
-machine state
and thus produce two (completely independent) IO
-machines get l state
and get r state
. We then evaluate their IO
effects one after another and return the op
-combination of their results.
Let's examine the kinds of IO
-machines built in main
. In the first line we produce a trivial IO
-machine, called state
, written return Map.empty
. This IO
-machine, each time it's run, performs no side effects in order to return a fresh, blank Map.Map
.
In the second line, we produce a new kind of IO
-machine called state'
. This IO
-machine is based off of the state
IO
-machine, but it also requests an input line. Thus, to be clear, each time state'
runs, a fresh Map.Map
is generated and then an input line is read to read some Int
, stored at "x"
.
It should be clear where this is going, but now when we examine the third line we see that we pass state'
, the IO
-machine, into eval
. Previously we stated that eval
runs its input IO
-machine twice, once for each name, and then combines the results. By this point it should be clear what's happening.
All together, we build a certain kind of machine which draws input and reads it as an integer, assigning it to a name in a blank Map.Map
. We then build this IO
-machine into a larger one which uses the first IO
-machine twice, in two separate invocations, in order to collect data and combine it with an Op
.
Finally, we run this eval
machine using do
notation (the (<-)
arrow indicates running the machine). Clearly it should collect two separate lines.
So what do we really want to do? Well, we need to simulate ambient state in the IO
monad, not just pass around Map.Map
s. This is easy to do by using an IORef
.
import Data.IORef
input :: IORef State -> String -> IO ()
input ref name = do
line <- getLine
modifyIORef ref (Map.insert name (read line))
eval :: IORef State -> Op -> String -> String -> IO Int
eval ref op l r = do
stateSnapshot <- readIORef ref
let Just i = Map.lookup l stateSnapshot
Just j = Map.lookup l stateSnapshot
return (op i j)
main = do
st <- newIORef Map.empty -- create a blank state, embedded into IO, not a value
input st "x" -- request input *once*
val <- eval st (+) "x" "x" -- compute the op
putStrLn . show $ val
回答2:
It's fine to wrap your actions such as getLine
in IO
, but to me it looks like your problem is that you're trying to pass your state in the IO
monad. Instead, I think this is probably time you get introduced to monad transformers and how they'll let you layer the IO
and State
monads to get the functionality of both in one.
Monad transformers are a pretty complex topic and it'll take a while to get to where you're comfortable with them (I'm still learning new things all the time about them), but they're a very useful tool when you need to layer multiple monads. You'll need the mtl
library to follow this example.
First, imports
import qualified Data.Map as Map
import Control.Monad.State
Then types
type Op = Int -> Int -> Int
-- Renamed to not conflict with Control.Monad.State.State
type AppState = Map.Map String Int
type Interpreter a = StateT AppState IO a
Here Interpreter
is the Monad
in which we'll build our interpreter. We also need a way to run the interpreter
-- A utility function for kicking off an interpreter
runInterpreter :: Interpreter a -> IO a
runInterpreter interp = evalStateT interp Map.empty
I figured defaulting to Map.empty
was sufficient.
Now, we can build our interpreter actions in our new monad. First we start with input
. Instead of returning our new state, we just modify what is current in our map:
input :: String -> Interpreter ()
input x = do
-- IO actions have to be passed to liftIO
line <- liftIO getLine
-- modify is a member of the MonadState typeclass, which StateT implements
modify (Map.insert x (read line))
I had to rename get
so that it didn't conflict with get
from Control.Monad.State
, but it does basically the same thing as before, it just takes our map and looks up that variable in it.
-- Had to rename to not conflict with Control.Monad.State.get
-- Also returns Maybe Int because it's safer
getVar :: String -> Interpreter (Maybe Int)
getVar x = do
-- get is a member of MonadState
vars <- get
return $ Map.lookup x vars
-- or
-- get x = fmap (Map.lookup x) get
Next, eval
now just looks up each variable in our map, then uses liftM2
to keep the return value as Maybe Int
. I prefer the safety of Maybe
, but you can rewrite it if you prefer
eval :: String -> Op -> String -> Interpreter (Maybe Int)
eval l op r = do
i <- getVar l
j <- getVar r
-- liftM2 op :: Maybe Int -> Maybe Int -> Maybe Int
return $ liftM2 op i j
Finally, we write our sample program. It stores user input to the variable "x"
, adds it to itself, and prints out the result.
-- Now we can write our actions in our own monad
program :: Interpreter ()
program = do
input "x"
y <- eval "x" (+) "x"
case y of
Just y' -> liftIO $ putStrLn $ "y = " ++ show y'
Nothing -> liftIO $ putStrLn "Error!"
-- main is kept very simple
main :: IO ()
main = runInterpreter program
The basic idea is that there is a "base" monad, here IO
, and these actions are "lifted" up to the "parent" monad, here StateT AppState
. There is a typeclass implementation for the different state operations get
, put
, and modify
in the MonadState
typeclass, which StateT
implements, and in order to lift IO
actions there's a pre-made liftIO
function that "lifts" IO
actions to the parent monad. Now we don't have to worry about passing around our state explicitly, we can still perform IO, and it has even simplified the code!
I would recommend reading the Real World Haskell chapter on monad transformers to get a better feel for them. There are other useful ones as well, such as ErrorT
for handling errors, ReaderT
for static configuration, WriterT
for aggregating results (usually used for logging), and many others. These can be layered into what is called a transformer stack, and it's not too difficult to make your own either.
回答3:
Instead of passing an IO State
, you can pass State
and then use higher-level functions to deal with IO. You can go further and make get
and eval
free from side-effects:
input :: String -> State -> IO State
input x state = do
line <- getLine
return $ Map.insert x (read line) state
get :: String -> State -> Int
get x state = case Map.lookup x state of
Just i -> i
eval :: String -> Op -> String -> State -> Int
eval l op r state = let i = get l state
j = get r state
in op i j
main :: IO ()
main = do
let state = Map.empty
state' <- input "x" state
let val = eval "x" (+) "x" state'
putStrLn . show $ val
回答4:
If you're actually building an interpreter, you'll presumably have a list of instructions to execute at some point.
This is my rough translation of your code (although I'm only a beginner myself)
import Data.Map (Map, empty, insert, (!))
import Control.Monad (foldM)
type ValMap = Map String Int
instrRead :: String -> ValMap -> IO ValMap
instrRead varname mem = do
putStr "Enter an int: "
line <- getLine
let intval = (read line)::Int
return $ insert varname intval mem
instrAdd :: String -> String -> String -> ValMap -> IO ValMap
instrAdd varname l r mem = do
return $ insert varname result mem
where result = (mem ! l) + (mem ! r)
apply :: ValMap -> (ValMap -> IO ValMap) -> IO ValMap
apply mem instr = instr mem
main = do
let mem0 = empty
let instructions = [ instrRead "x", instrAdd "y" "x" "x" ]
final <- foldM apply mem0 instructions
print (final ! "y")
putStrLn "done"
The foldM
applies a function (apply
) to a start value (mem0
) and a list (instructions
) but does so within a monad.
来源:https://stackoverflow.com/questions/22568771/get-value-from-io-rather-than-the-computation-itself