Portability | Rank2Types |
---|---|
Stability | experimental |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | None |
- (<>~) :: Monoid c => Setting a b c c -> c -> a -> b
- (<<>~) :: Monoid m => LensLike ((,) m) a b m m -> m -> a -> (m, b)
- (<>=) :: (MonadState a m, Monoid b) => SimpleSetting a b -> b -> m ()
- (<<>=) :: (MonadState a m, Monoid r) => SimpleLensLike ((,) r) a 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 c => Setting a b c c -> c -> a -> bSource
Modify the target of a monoidally valued by mappend
ing another value.
>>>
:m + Control.Lens
>>>
both <>~ "!!!" $ ("hello","world")
("hello!!!","world!!!")
(<>~
) ::Monoid
c =>Setter
a b c c -> c -> a -> b (<>~
) ::Monoid
c =>Iso
a b c c -> c -> a -> b (<>~
) ::Monoid
c =>Lens
a b c c -> c -> a -> b (<>~
) ::Monoid
c =>Traversal
a b c c -> c -> a -> b
(<>=) :: (MonadState a m, Monoid b) => SimpleSetting a b -> b -> m ()Source
Modify the target(s) of a Simple
Lens
, Iso
, Setter
or Traversal
by mappend
ing a value.
(<>=
) :: (MonadState
a m,Monoid
b) =>Simple
Setter
a b -> b -> m () (<>=
) :: (MonadState
a m,Monoid
b) =>Simple
Iso
a b -> b -> m () (<>=
) :: (MonadState
a m,Monoid
b) =>Simple
Lens
a b -> b -> m () (<>=
) :: (MonadState
a m,Monoid
b) =>Simple
Traversal
a b -> b -> m ()
(<<>=) :: (MonadState a m, Monoid r) => SimpleLensLike ((,) r) a 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