问题
I've been trying to wrap my head around the concept of monads and I've been experimenting with the following example:
I have an Editor
data-type that represents the state of a text document and some functions that work on it.
data Editor = Editor {
lines :: [Line], -- editor contents are kept line by line
lineCount :: Int, -- holds length lines at all times
caret :: Caret -- the current caret position
-- ... some more definitions
} deriving (Show)
-- get the line at the given position (first line is at 0)
lineAt :: Editor -> Int -> Line
lineAt ed n = ls !! n
where
ls = lines ed
-- get the line that the caret is currently on
currentLine :: Editor -> Line
currentLine ed = lineAt ed $ currentY ed
-- move the caret horizontally by the specified amount of characters (can not
-- go beyond the current line)
moveHorizontally :: Editor -> Int -> Editor
moveHorizontally ed n = ed { caret = newPos }
where
Caret x y = caret ed
l = currentLine ed
mx = fromIntegral (L.length l - 1)
newX = clamp 0 mx (x+n)
newPos = Caret newX y
-- ... and lots more functions to work with an Editor
All of these functions act on an Editor
, and many of them return a new Editor
(where the caret has been moved or some text has been changed) so I thought this might be a good application of the State
monad and I have re-written most Editor
-functions to now look like this:
lineAt' :: Int -> State Editor Line
lineAt' n = state $ \ed -> (lines ed !! n, ed)
currentLine' :: State Editor Line
currentLine' = do
y <- currentY'
lineAt' y
moveHorizontally' :: Int -> State Editor ()
moveHorizontally' n = do
(Caret x y) <- gets caret
l <- currentLine'
let mx = fromIntegral (L.length l - 1)
let newX = clamp 0 mx (x+n)
modify (\ed -> ed { caret = Caret newX y })
moveHorizontally' :: Int -> State Editor ()
moveHorizontally' n = do
(Caret x y) <- gets caret
l <- currentLine'
let mx = fromIntegral (L.length l - 1)
let newX = clamp 0 mx (x+n)
modify (\ed -> ed { caret = Caret newX y })
This is pretty awesome, because it allows me to compose editing actions very easily within do
-notation.
However, now I'm struggling to put this to use within an actual application. Say I want to use this Editor
within an application that performs some IO. Say I want to manipulate an instance of Editor
everytime the user presses the l
key on the keyboard.
I would need to have another State
monad representing the overall application state that holds an Editor
instance and a sort-of event-loop that uses the IO
monad to read from the keyboard and calls moveHorizontally'
to modify the current AppState by modifying its Editor
.
I've read up a bit on this topic and it seems like I need to use Monad Transformers to build a stack of monads with IO at the bottom. I've never used Monad Transformers before and I don't know what to do from here? I've also found out that the State
monad already implements some functionality (it seems to be a special case of a Monad Transformer?) but I'm confused on how to use that?
回答1:
First, let's back up a bit. It's always best to have problems isolated. Let pure functions be grouped with pure functions, State - with State and IO - with IO. Intertwining multiple concepts is a certain recipe for cooking code-spaghetti. You don't want that meal.
Having said that, let's restore the pure functions that you had and group them in a module. However we'll apply small modifications to make them conform to the Haskell conventions - namely, we'll change the parameter order:
-- |
-- In this module we provide all the essential functions for
-- manipulation of the Editor type.
module MyLib.Editor where
data Editor = ...
lineAt :: Int -> Editor -> Line
moveHorizontally :: Int -> Editor -> Editor
Now, if you really want to get your State
API back, it's trivial to implement in another module:
-- |
-- In this module we address the State monad.
module MyLib.State where
import qualified MyLib.Editor as A
lineAt :: Int -> State A.Editor Line
lineAt at = gets (A.lineAt at)
moveHorizontally :: Int -> State A.Editor ()
moveHorizontally by = modify (A.moveHorizontally by)
As you see now, following the standard conventions allows us to use the standard State
utilities like gets and modify to trivially lift the already implemented functions to the State
monad.
However, actually the mentioned utilities work for the StateT
monad-transformer as well, of which State
is actually just a special case. So we can just as well implement the same thing in a more general way:
-- |
-- In this module we address the StateT monad-transformer.
module MyLib.StateT where
import qualified MyLib.Editor as A
lineAt :: Monad m => Int -> StateT A.Editor m Line
lineAt at = gets (A.lineAt at)
moveHorizontally :: Monad m => Int -> StateT A.Editor m ()
moveHorizontally by = modify (A.moveHorizontally by)
As you see, all that's changed are the type signatures.
Now you can use those general functions in your transformer stack. E.g.,
-- |
-- In this module we address the problems of the transformer stack.
module MyLib.Session where
import qualified MyLib.Editor as A
import qualified MyLib.StateT as B
-- | Your trasformer stack
type Session = StateT A.Editor IO
runSession :: Session a -> A.Editor -> IO (a, A.Editor)
runSession = runStateT
lineAt :: Int -> Session Line
lineAt = B.lineAt
moveHorizontally :: Int -> Session ()
moveHorizontally = B.moveHorizontally
-- |
-- A function to lift the IO computation into our stack.
-- Luckily for us it is already presented by the MonadIO type-class.
-- liftIO :: IO a -> Session a
Thus we've just achieved a granular isolation of concerns and a great flexibility of our codebase.
Now, of course, this makes a quite primitive example so far. Usually the final monad-transformer stack has more levels. E.g.,
type Session = ExceptT Text (ReaderT Database (StateT A.Editor IO))
To jump between all those levels the typical tool-set is the lift function or the "mtl" library, which provides type-classes to reduce the usage of lift
. I have to mention though, that not everyone (myself including) is a fan of "mtl", because, while reducing the amount of code it introduces a certain ambiguity and reasoning complexity. I prefer to use lift
explicitly.
The point of transformers is to allow you to extend an existing monad (transformer stack is a monad as well) with some new functionality in an ad-hoc way.
As for your question about extending the app's state, you can simply add another StateT layer to your stack:
-- |
-- In this module we address the problems of the transformer stack.
module MyLib.Session where
import qualified MyLib.Editor as A
-- In presence of competing modules,
-- it's best to rename StateT to the more specific EditorStateT
import qualified MyLib.EditorStateT as B
import qualified MyLib.CounterStateT as C
-- | Your trasformer stack
type Session = StateT Int (StateT A.Editor IO)
lineAt :: Int -> Session Line
lineAt = lift B.lineAt
moveHorizontally :: Int -> Session ()
moveHorizontally = lift B.moveHorizontally
-- | An example of addressing a different level of the stack.
incCounter :: Session ()
incCounter = C.inc
-- | An example of how you can dive deeply into your stack.
liftIO :: IO a -> Session a
liftIO io = lift (lift io)
回答2:
Using mtl you won't need to commit to any monad stack in particular until the point of your program where you actually run the effects. This means that you can easily change the stack to add extra layers, pick a different error-reporting strategy, etc., etc.
All you need to do is enable the -XFlexibleContexts
language extension by adding the following line at the top of your file:
{-# LANGUAGE FlexibleContexts #-}
Import the module defining the MonadState
class:
import Control.Monad.State
Change the type annotation of your programs to reflect the fact that you are now using this approach. The MonadState Editor m =>
constraints says that m
is a monad which has a state of type Editor
somewhere in it.
lineAt' :: MonadState Editor m => Int -> m Line
currentY' :: MonadState Editor m => m Int
currentLine' :: MonadState Editor m => m Line
Let's say that you now want to read a line from stdin
and push it onto the list of lines (in practice you'd probably want to insert the characters after the current carret and move it accordingly but the general idea is the same). You can simply use the MonadIO
constraint to indicate that you need some IO
capability for this function:
newLine :: (MonadIO m, MonadState Editor m) => m ()
newLine = do
nl <- liftIO getLine
modify $ \ ed -> ed { lines = nl : lines ed }
来源:https://stackoverflow.com/questions/38890218/state-and-io-monads