| Portability | Rank2Types |
|---|---|
| Stability | experimental |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Safe Haskell | Safe-Inferred |
Data.Monoid.Lens
Description
- (<>~) :: Monoid a => Setting s t a a -> a -> s -> t
- (<<>~) :: Monoid m => LensLike ((,) m) s t m m -> m -> s -> (m, t)
- (<>=) :: (MonadState s m, Monoid a) => SimpleSetting s a -> a -> m ()
- (<<>=) :: (MonadState s m, Monoid r) => SimpleLensLike ((,) r) s r -> r -> m r
- _dual :: Iso a b (Dual a) (Dual b)
- _endo :: Iso (a -> a) (b -> b) (Endo a) (Endo b)
- _all :: Simple Iso Bool All
- _any :: Simple Iso Bool Any
- _sum :: Iso a b (Sum a) (Sum b)
- _product :: Iso a b (Product a) (Product b)
- _first :: Iso (Maybe a) (Maybe b) (First a) (First b)
- _last :: Iso (Maybe a) (Maybe b) (Last a) (Last b)
Documentation
(<>~) :: Monoid a => Setting s t a a -> a -> s -> tSource
Modify the target of a monoidally valued by mappending another value.
>>>:m + Control.Lens>>>both <>~ "!!!" $ ("hello","world")("hello!!!","world!!!")
(<>~) ::Monoida =>Setters t a a -> a -> s -> t (<>~) ::Monoida =>Isos t a a -> a -> s -> t (<>~) ::Monoida =>Lenss t a a -> a -> s -> t (<>~) ::Monoida =>Traversals t a a -> a -> s -> t
(<>=) :: (MonadState s m, Monoid a) => SimpleSetting s a -> a -> m ()Source
Modify the target(s) of a Simple Lens, Iso, Setter or Traversal by mappending a value.
(<>=) :: (MonadStates m,Monoida) =>SimpleSetters a -> a -> m () (<>=) :: (MonadStates m,Monoida) =>SimpleIsos a -> a -> m () (<>=) :: (MonadStates m,Monoida) =>SimpleLenss a -> a -> m () (<>=) :: (MonadStates m,Monoida) =>SimpleTraversals a -> a -> m ()
(<<>=) :: (MonadState s m, Monoid r) => SimpleLensLike ((,) r) s r -> r -> m rSource
_all :: Simple Iso Bool AllSource
Isomorphism for All
>>>:m + Control.Lens Data.Monoid.Lens Data.Foldable>>>ala _all foldMap [True,True]True
>>>:m + Control.Lens Data.Monoid.Lens Data.Foldable>>>ala _all foldMap [True,False]False
_any :: Simple Iso Bool AnySource
Isomorphism for Any
>>>:m + Control.Lens Data.Monoid.Lens Data.Foldable>>>ala _any foldMap [False,False]False
>>>:m + Control.Lens Data.Monoid.Lens Data.Foldable>>>ala _any foldMap [True,False]True
_sum :: Iso a b (Sum a) (Sum b)Source
Isomorphism for Sum
>>>:m + Control.Lens Data.Monoid.Lens Data.Foldable>>>ala _sum foldMap [1,2,3,4]10