monad-var-0.2.1.0: Generic operations over variables

Safe HaskellSafe
LanguageHaskell2010

MonadVar.Lens

Synopsis

Documentation

(./) :: LensLike (Const s) v x s y -> LensLike f s t a b -> LensLike f v t a b infixr 8 Source #

Go down by the first lens into a data structure and apply the second lens to the result. This throws away the part of the structure skipped by the first lens, e.g.

('a', ('b', 'c')) & _2 ./ _2 %~ succ

results in

('b','d')

effectful :: Functor f => Lens s t a b -> Lens s (f t) a (f b) Source #

Make a lens that runs with an effect out of a simple lens. E.g.

("a", "b") & effectful _2 .~ getLine

asks for a string and replaces the second element of the tuple with it.

(.!) :: (Functor f, Functor g) => Lens v w s t -> LensLike g s (f t) a b -> LensLike g v (f w) a b infixr 9 Source #

Compose a simple lens and a lens that runs with some effect.

_VarM :: forall m n v a. MonadMutateM_ m n v => ASetter (v a) (n ()) a (m a) Source #

A monadic setter for a variable. E.g.

do
  v <- newIORef 'a'
  v & _VarM %~ \a -> succ a <$ putStr (show a)
  readIORef v >>= print

prints

'a''b'

_Var :: forall m v a. MonadMutate_ m v => ASetter (v a) (m ()) a a Source #

A setter for a variable. E.g.

do
  v <- newIORef 'a'
  v & _Var %~ succ
  readIORef v >>= print

prints

'b'