问题
An idiom I use for composing a couple of procedures (with memory) is as follows:
p1 :: State (Int, String) ()
p1 = do
(a, b) <- get
... do something ...
put (a', b)
p2 :: State (Int, String) ()
p2 = do
(a, b) <- get
... do something else ...
put (a, b')
main = do
... initializing a0 b0 ...
print . flip evalState (a0, b0)
. sequence $ replicate 10 p1 ++ repeat p2
However, as the number of state variable grows, this quickly gets way more verbose than necessary:
p1 :: State (Int, String, Bool, Int, String, Bool) ()
p1 = do
(a, b, c, d, e, f) <- get
... do something ...
put (a, b, c', d, e, f')
p2 :: State (Int, String, Bool, Int, String, Bool) ()
p2 = do
(a, b, c, d, e, f) <- get
... do something ...
put (a', b', c, d, e, f)
main = do
print . flip evalState (a0, b0, c0, d0, e0, f0)
. sequence $ replicate 10 p1 ++ repeat p2
As I was wondering, is there a way of updating only a few state variables without having to refer to all the unused ones? I was thinking something like IORef
but for State
(in fact there is a package stateref), but I'm not sure if there are already some common idioms that other people have been using.
回答1:
This seems like a job for lenses. Especially the Control.Lens.Tuple module together with .=
and use
:
p1 = do
a <- use _1
-- do something --
_1 .= a'
However, it's usually better if you give the things in your state proper names, e.g.
{-# LANGUAGE TemplateHaskell #-
data Record = MkRecord { _age :: Int
, _name :: String
, _programmer :: Bool
} deriving (Show, Eq)
makeLenses ''Record
That way, you have better names for your field:
p1 = do
a <- use age
-- do something --
age .= a'
Note that this still helps you if you don't want to use lenses, since you can use record syntax to update your data:
p1 = do
r <- get
let a = _age r
--- do something
put $ r{_age = a'}
回答2:
This is a good situation to use records, with the gets
and modify
functions to manipulate subparts of the state:
data Env = Env
{ envNumber :: Int
, envText :: String
}
p1 :: State Env ()
p1 = do
a <- gets envNumber
-- ...
modify $ \r -> r { envNumber = a' }
p2 :: State Env ()
p2 = do
b <- gets envText
-- ...
modify $ \r -> r { envText = b' }
gets
turns a pure getter function into a state action:
gets :: (s -> a) -> State s a
envNumber :: Env -> Int
gets envNumber :: State Env Int
And modify
turns a pure update function into a state action:
modify :: (s -> s) -> State s ()
(\r -> r { envText = b' }) :: Env -> Env
modify (\r -> ...) :: State Env ()
回答3:
lens
's zoom combinator lifts a computation in a State
monad into a computation that runs in a "larger" State
monad.
zoom :: Lens' s t -> State t a -> State s a
So, given a "big" state:
data Big = Big {
_big1 :: Medium,
_big2 :: Medium
}
data Medium = Medium {
_medium1 :: Small,
_medium2 :: Small
}
data Small = Small { _small :: Int }
makeLenses ''Big
makeLenses ''Medium
makeLenses ''Small
you can "zoom in" on a part of the state:
incr :: State Int ()
incr = id += 1
incrSmall :: State Big ()
incrSmall = zoom (big2.medium1.small) incr
Of course, this'll work on big tuples as well as records, using lens
's built-in tuple field accessors.
zoom
's real type signature is more general than the simple one I quoted above. It uses MonadState
constraints to work under a monad transformer stack, rather than in State
specifically.
来源:https://stackoverflow.com/questions/40523355/how-do-i-avoid-referring-to-all-state-variables-when-updating-only-a-few