问题
I often end up in a situation where it's very convenient to be using the State
monad, due to having a lot of related functions that need to operate on the same piece of data in a semi-imperative way.
Some of the functions need to read the data in the State monad, but will never need to change it. Using the State
monad as usual in these functions works just fine, but I can't help but feel that I've given up Haskell's inherent safety and replicated a language where any function can mutate anything.
Is there some type-level thing that I can do to ensure that these functions can only read from the State
, and never write to it?
Current situation:
iWriteData :: Int -> State MyState ()
iWriteData n = do
state <- get
put (doSomething n state)
-- Ideally this type would show that the state can't change.
iReadData :: State MyState Int
iReadData = do
state <- get
return (getPieceOf state)
bigFunction :: State MyState ()
bigFunction = do
iWriteData 5
iWriteData 10
num <- iReadData -- How do we know that the state wasn't modified?
iWRiteData num
Ideally iReadData
would probably have the type Reader MyState Int
, but then it doesn't play nicely with the State
. Having iReadData
be a regular function seems to be the best bet, but then I have to go through the gymnastics of explicitly extracting and passing it the state every time it's used. What are my options?
回答1:
It's not hard to inject the Reader
monad into State
:
read :: Reader s a -> State s a
read a = gets (runReader a)
then you could say
iReadData :: Reader MyState Int
iReadData = do
state <- ask
return (getPieceOf state)
and call it as
x <- read $ iReadData
this would allow you to build up Reader
s into larger read-only sub-programs and inject them into State
only where you need to combine them with mutators.
It's not hard to extend this to a ReaderT
and StateT
at the top of your monad transformer stack (in fact, the definition above works exactly for this case, just change the type). Extending it to a ReaderT
and StateT
in the middle of the stack is harder. You basically need a function
lift1 :: (forall a. m0 a -> m1 a) -> t m0 a -> t m1 a
for every monad transformer t
in the stack above the ReaderT
/StateT
, which isn't part of the standard library.
回答2:
I would recommend wrapping up the State
monad in a newtype
and defining a MonadReader
instance for it:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
import Control.Applicative
import Control.Monad.State
import Control.Monad.Reader
data MyState = MyState Int deriving Show
newtype App a = App
{ runApp' :: State MyState a
} deriving
( Functor
, Applicative
, Monad
, MonadState MyState
)
runApp :: App a -> MyState -> (a, MyState)
runApp app = runState $ runApp' app
instance MonadReader MyState App where
ask = get
local f m = App $ fmap (fst . runApp m . f) $ get
iWriteData :: MonadState MyState m => Int -> m ()
iWriteData n = do
MyState s <- get
put $ MyState $ s + n
iReadData :: MonadReader MyState m => m Int
iReadData = do
MyState s <- ask
return $ s * 2
bigFunction :: App ()
bigFunction = do
iWriteData 5
iWriteData 10
num <- iReadData
iWriteData num
This is certainly more code that @jcast's solution, but it follows the the tradition of implementing your transformer stack as a newtype wrapper, and by sticking with constraints instead of solidified types you can make strong guarantees about the use of your code while providing maximum flexibility for re-use. Anyone using your code would be able to extend your App
with transformers of their own while still using iReadData
and iWriteData
as intended. You also don't have to wrap every call to a Reader
monad with a read
function, the MonadReader MyState
functions are seamlessly integrated with functions in the App
monad.
回答3:
Excellent answers by jcast and bhelkir, with exactly the first idea I thought of—embedding Reader
inside State
.
I think it's worthwhile to address this semi-side point of your question:
Using the
State
monad as usual in these functions works just fine, but I can't help but feel that I've given up Haskell's inherent safety and replicated a language where any function can mutate anything.
That's a potential red flag, indeed. I've always found that State
works best for code with "small" states that can be contained within the lifetime of a single, brief application of runState
. My go-to example is numbering the elements of a Traversable
data structure:
import Control.Monad.State
import Data.Traversable (Traversable, traverse)
tag :: (Traversable t, Enum s) => s -> t a -> t (s, a)
tag i ta = evalState (traverse step ta) init
where step a = do s <- postIncrement
return (s, a)
postIncrement :: Enum s => State s s
postIncrement = do result <- get
put (succ result)
return result
You don't directly say so, but you make it sound you may have a big state value, with many different fields being used in many different ways within a long-lived runState
call. And perhaps it does need to be that way for your program at this point. But one technique for coping with this might be to write your smaller State
actions so that they only use narrower state types than the "big" one and then embed these into the larger State
type with a function like this:
-- | Extract a piece of the current state and run an action that reads
-- and modifies only that piece.
substate :: (s -> s') -> (s' -> s -> s) -> State s' a -> State s a
substate extract replace action =
do s <- get
let (s', a) = runState action (extract s)
put (replace s' s)
return a
Schematic example
example :: State (A, B) Whatever
example = do foo <- substate fst (,b) action1
bar <- substate snd (a,) action2
return $ makeWhatever foo bar
-- Can only touch the `A` component of the state
action1 :: State A Foo
action1 = ...
-- Can only touch the `B` component of the state
action2 :: State B Bar
action2 = ...
Note that the extract
and replace
functions constitute a lens, and there are libraries for that, which may even already include a function like this.
来源:https://stackoverflow.com/questions/28587132/making-read-only-functions-for-a-state-in-haskell