lens-2.2: Lenses, Folds and Traversals

PortabilityMTPCs, FDs, Rank2
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-Infered

Control.Lens.Action

Contents

Description

 

Synopsis

Composable Actions

type Action m a c = forall f r. Effective m r f => (c -> f c) -> a -> f aSource

An Action is a Getter enriched with access to a Monad for side-effects.

Every Getter can be used as an Action

You can compose an Action with another Action using (.) from the Prelude.

act :: Monad m => (a -> m c) -> Action m a cSource

Construct an Action from a monadic side-effect

acts :: Action m (m a) aSource

A self-running Action, analogous to join.

acts = act id
>>> import Control.Lens
>>> (1,"hello")^!_2.acts.to succ
"ifmmp"

perform :: Monad m => Acting m c a c -> a -> m cSource

Perform an Action.

 perform = flip (^!)

liftAct :: (MonadTrans t, Monad m) => Acting m c a c -> Action (t m) a cSource

Apply a Monad transformer to an Action.

(^!) :: Monad m => a -> Acting m c a c -> m cSource

Perform an Action

>>> import Control.Lens
>>> ["hello","world"]^!folded.act putStrLn
hello
world

Folds with Effecs

type MonadicFold m a c = forall f r. (Effective m r f, Applicative f) => (c -> f c) -> a -> f aSource

A MonadicFold is a Fold enriched with access to a Monad for side-effects.

Every Fold can be used as a MonadicFold, that simply ignores the access to the Monad.

You can compose a MonadicFold with another MonadicFold using (.) from the Prelude.

Implementation Details

type Acting m r a c = (c -> Effect m r c) -> a -> Effect m r aSource

Used to evaluate an Action.

class (Monad m, Gettable f) => Effective m r f | f -> m r whereSource

An Effective Functor ignores its argument and is isomorphic to a monad wrapped around a value.

That said, the monad is possibly rather unrelated to any Applicative structure.

Methods

effective :: Isomorphic k => k (m r) (f a)Source

Instances

Effective Identity r (Accessor r) 
Monad m => Effective m r (Effect m r) 
Effective m r f => Effective m (Dual r) (Backwards f) 

ineffective :: Effective m r f => Isomorphic k => k (f a) (m r)Source

A convenient antonym that is used internally.

newtype Effect m r a Source

Wrap a monadic effect with a phantom type argument.

Constructors

Effect 

Fields

getEffect :: m r
 

Instances

Monad m => Effective m r (Effect m r) 
Monad m => Functor (Effect m r) 
(Monad m, Monoid r) => Applicative (Effect m r) 
Monad m => Gettable (Effect m r) 
(Monad m, Monoid r) => Monoid (Effect m r a)