Reputation: 4984
I have an OuterState
object that contains multiple _objects
that should be modified using nestedAction
which also requires access to the OuterState
object. Hence, nestedAction
is a nested state transformer that is run for each InnerStateObject
like in this example:
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Control.Lens ((+=), makeLenses)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.State.Lazy
(StateT, evalStateT, execStateT, get)
import Control.Monad.Trans.Class (lift)
data OuterState = OuterState
{ _objects :: [InnerStateObject]
, _count :: Int
} deriving (Show)
data InnerStateObject = InnerStateObject
{ _value :: Int
} deriving (Show)
makeLenses ''OuterState
makeLenses ''InnerStateObject
startNestedAction :: StateT OuterState IO ()
startNestedAction = do
get >>= liftIO . putStrLn . ("before: " ++) . show
objects . traverse <~% execStateT nestedAction
get >>= liftIO . putStrLn . ("after: " ++) . show
nestedAction :: StateT InnerStateObject (StateT OuterState IO) ()
nestedAction = do
value += 10
lift $ count += 100
main :: IO ()
main =
evalStateT
startNestedAction
OuterState {_count = 0, _objects = map InnerStateObject [0 .. 2]}
The definition of <~%
is missing in this example. The precedence is infixr 2 <~%
. It should pass each value of objects . traverse
to execStateT nestedAction
and assign the result to objects . traverse
.
How can I implement <~%
? What is the type of it?
dependencies: lts-9.3
Upvotes: 1
Views: 98
Reputation: 33389
use objects >>= traverse (execStateT nestedAction) >>= assign objects
object . traverse
is too coarse grained to elegantly express the update of the count
field (implicit via nestedAction
) during the traversal of the objects
field. This is basically why the lens library has no operator (<~%) :: MonadState s m => ATraversal' s a -> (a -> m a) -> m ()
: it does not behave well if its second argument modifies parts of the state that are also being targeted by the traversal in its first argument.
Upvotes: 1