profunctor-optics-0.0.2: A compact optics library compatible with the typeclasses in profunctors.

Safe HaskellNone
LanguageHaskell2010

Data.Profunctor.Optic.Setter

Contents

Synopsis

Setter

type Setter s t a b = forall p. (Affine p, Traversing p, Mapping p) => Optic p s t a b Source #

\( \mathsf{Setter}\;S\;A = \exists F : \mathsf{Functor}, S \equiv F\,A \)

type Setter' s a = Setter s s a a Source #

setter :: ((a -> b) -> s -> t) -> Setter s t a b Source #

Obtain a Setter from a SEC.

To demote an optic to a semantic edit combinator, use the section (l ..~) or over l.

>>> [("The",0),("quick",1),("brown",1),("fox",2)] & setter fmap . first' ..~ Prelude.length
[(3,0),(5,1),(5,1),(3,2)]

Caution: In order for the generated optic to be well-defined, you must ensure that the input function satisfies the following properties:

  • abst id ≡ id
  • abst f . abst g ≡ abst (f . g)

More generally, a profunctor optic must be monoidal as a natural transformation:

See Property.

closing :: (((s -> a) -> b) -> t) -> Setter s t a b Source #

Every valid Grate is a Setter.

Resetter

type Resetter s t a b = forall p. (Coaffine p, Cotraversing p, Comapping p) => Optic p s t a b Source #

\( \mathsf{Setter}\;S\;A = \exists F : \mathsf{Functor}, F\,S \equiv A \)

type Resetter' s a = Resetter s s a a Source #

resetter :: ((a -> t) -> s -> t) -> Resetter s t a t Source #

Obtain a Resetter from a SEC.

Caution: In order for the generated optic to be well-defined, you must ensure that the input function satisfies the following properties:

  • abst id ≡ id
  • abst f . abst g ≡ abst (f . g)

Optics

cod :: Profunctor p => Setter (p r a) (p r b) a b Source #

Map covariantly over the output of a Profunctor.

The most common profunctor to use this with is (->).

(dom ..~ f) g x ≡ f (g x)
cod @(->) ≡ withGrate closed closing
>>> (cod ..~ show) length [1,2,3]
"3"

dom :: Profunctor p => Setter (p b r) (p a r) a b Source #

Map contravariantly over the input of a Profunctor.

The most common profunctor to use this with is (->).

(dom ..~ f) g x ≡ g (f x)
>>> (dom ..~ show) length [1,2,3]
7

bound :: Monad m => Setter (m a) (m b) a (m b) Source #

Setter for monadically transforming a monadic value.

fmapped :: Functor f => Setter (f a) (f b) a b Source #

Setter on each value of a functor.

contramapped :: Contravariant f => Setter (f b) (f a) a b Source #

Setter on each value of a contravariant functor.

contramapover contramapped
>>> getPredicate (over contramapped (*2) (Predicate even)) 5
True
>>> getOp (over contramapped (*5) (Op show)) 100
"500"

liftedA :: Applicative f => Setter (f a) (f b) a b Source #

Setter on each value of an applicative.

liftAsetter liftedA
>>> setter liftedA Identity [1,2,3]
[Identity 1,Identity 2,Identity 3]
>>> set liftedA 2 (Just 1)
Just 2

liftedM :: Monad m => Setter (m a) (m b) a b Source #

Setter on each value of a monad.

forwarded :: Setter (ReaderT r2 m a) (ReaderT r1 m a) r1 r2 Source #

Setter on the local environment of a Reader.

Use to lift reader actions into a larger environment:

>>> runReader (ask & forwarded ..~ fst) (1,2)
1

censored :: MonadWriter w m => Setter' (m a) w Source #

TODO: Document

zipped :: Setter (u -> v -> a) (u -> v -> b) a b Source #

Setter on the codomain of a zipping function.

>>> ((,) & zipped ..~ swap) 1 2
(2,1)

modded :: (a -> Bool) -> Setter' (a -> b) b Source #

TODO: Document

cond :: (a -> Bool) -> Setter' a a Source #

Apply a function only when the given condition holds.

See also predicated & filtered.

Operators

set :: Optic (->) s t a b -> b -> s -> t Source #

Prefix variant of .~.

 set l y (set l x a) ≡ set l y a

over :: Optic (->) s t a b -> (a -> b) -> s -> t Source #

Prefix alias of ..~.

over o idid 
over o f . over o g ≡ over o (f . g)
over . setterid
over . resetterid
>>> over fmapped (+1) (Just 1)
Just 2
>>> over fmapped (*10) [1,2,3]
[10,20,30]
>>> over first' (+1) (1,2)
(2,2)
>>> over first' show (10,20)
("10",20)

(.~) :: Optic (->) s t a b -> b -> s -> t infixr 4 Source #

Set all referenced fields to the given value.

(..~) :: Optic (->) s t a b -> (a -> b) -> s -> t infixr 4 Source #

Map over an optic.

>>> Just 1 & just ..~ (+1)
Just 2
>>> Nothing & just ..~ (+1)
Nothing
>>> [1,2,3] & fmapped ..~ (*10)
[10,20,30]
>>> (1,2) & first' ..~ (+1)
(2,2)
>>> (10,20) & first' ..~ show
("10",20)

(<>~) :: Semigroup a => Optic (->) s t a a -> a -> s -> t infixr 4 Source #

Modify the target by adding another value.

>>> both <>~ "!" $ ("bar","baz")
("bar!","baz!")

mtl

locally :: MonadReader s m => Optic (->) s s a b -> (a -> b) -> m r -> m r Source #

Modify the value of a Reader environment.

locally l id a ≡ a
locally l f . locally l g ≡ locally l (f . g)
>>> (1,1) & locally first' (+1) (uncurry (+))
3
>>> "," & locally (setter ($)) ("Hello" <>) (<> " world!")
"Hello, world!"

Compare forwarded.

scribe :: MonadWriter w m => Monoid b => Optic (->) s w a b -> s -> m () Source #

Write to a fragment of a larger Writer format.

assigns :: MonadState s m => Optic (->) s s a b -> b -> m () Source #

Replace the target(s) of a settable in a monadic state.

modifies :: MonadState s m => Optic (->) s s a b -> (a -> b) -> m () Source #

Map over the target(s) of a Setter in a monadic state.

(.=) :: MonadState s m => Optic (->) s s a b -> b -> m () infix 4 Source #

Replace the target(s) of a settable in a monadic state.

This is an infixversion of assigns.

>>> execState (do first' .= 1; second' .= 2) (3,4)
(1,2)
>>> execState (both .= 3) (1,2)
(3,3)

(..=) :: MonadState s m => Optic (->) s s a b -> (a -> b) -> m () infix 4 Source #

Map over the target(s) of a Setter in a monadic state.

This is an infixversion of modifies.

>>> execState (do just ..= (+1) ) Nothing
Nothing
>>> execState (do first' ..= (+1) ;second' ..= (+2)) (1,2)
(2,4)
>>> execState (do both ..= (+1)) (1,2)
(2,3)

(<>=) :: MonadState s m => Semigroup a => Optic' (->) s a -> a -> m () infix 4 Source #

Modify the target(s) of a settable optic by adding a value.

>>> execState (both <>= "!!!") ("hello","world")
("hello!!!","world!!!")