profunctor-optics-0.0.0.4: An optics library compatible with the typeclasses in 'profunctors'.

Safe HaskellSafe
LanguageHaskell2010

Data.Profunctor.Optic.Traversal

Contents

Synopsis

Traversal & Ixtraversal

type Traversal s t a b = forall p. (Choice p, Strong p, Representable p, Applicative (Rep p)) => Optic p s t a b Source #

A Traversal processes 0 or more parts of the whole, with Applicative interactions.

\( \mathsf{Traversal}\;S\;A = \exists F : \mathsf{Traversable}, S \equiv F\,A \)

type Traversal' s a = Traversal s s a a Source #

type Ixtraversal i s t a b = forall p. (Choice p, Strong p, Representable p, Applicative (Rep p)) => IndexedOptic p i s t a b Source #

type Ixtraversal' i s a = Ixtraversal i s s a a Source #

traversing :: Traversable f => (s -> a) -> (s -> b -> t) -> Traversal (f s) (f t) a b Source #

Obtain a Traversal by lifting a lens getter and setter into a Traversable functor.

 withLens o traversingtraversed . o

Compare folding.

Caution: In order for the generated optic to be well-defined, you must ensure that the input functions constitute a legal lens:

  • sa (sbt s a) ≡ a
  • sbt s (sa s) ≡ s
  • sbt (sbt s a1) a2 ≡ sbt s a2

See Property.

The resulting optic can detect copies of the lens stucture inside any Traversable container. For example:

>>> lists (traversing snd $ \(s,_) b -> (s,b)) [(0,'f'),(1,'o'),(2,'o'),(3,'b'),(4,'a'),(5,'r')]
"foobar"

itraversing :: Monoid i => Traversable f => (s -> (i, a)) -> (s -> b -> t) -> Ixtraversal i (f s) (f t) a b Source #

Obtain a Ixtraversal by lifting an indexed lens getter and setter into a Traversable functor.

 withIxlens o itraversingitraversed . o

Caution: In order for the generated optic to be well-defined, you must ensure that the input functions constitute a legal indexed lens:

  • snd . sia (sbt s a) ≡ a
  • sbt s (snd $ sia s) ≡ s
  • sbt (sbt s a1) a2 ≡ sbt s a2

See Property.

traversalVl :: (forall f. Applicative f => (a -> f b) -> s -> f t) -> Traversal s t a b Source #

Obtain a profunctor Traversal from a Van Laarhoven Traversal.

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

  • abst pure ≡ pure
  • fmap (abst f) . abst g ≡ getCompose . abst (Compose . fmap f . g)

See Property.

itraversalVl :: (forall f. Applicative f => (i -> a -> f b) -> s -> f t) -> Ixtraversal i s t a b Source #

Lift an indexed VL traversal into an indexed profunctor traversal.

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

  • iabst (const pure) ≡ pure
  • fmap (iabst $ const f) . (iabst $ const g) ≡ getCompose . iabst (const $ Compose . fmap f . g)

See Property.

noix :: Monoid i => Traversal s t a b -> Ixtraversal i s t a b Source #

Lift a VL traversal into an indexed profunctor traversal that ignores its input.

Useful as the first optic in a chain when no indexed equivalent is at hand.

>>> ilists (noix traversed . itraversed) ["foo", "bar"]
[(0,'f'),(1,'o'),(2,'o'),(0,'b'),(1,'a'),(2,'r')]
>>> ilists (itraversed . noix traversed) ["foo", "bar"]
[(0,'f'),(0,'o'),(0,'o'),(0,'b'),(0,'a'),(0,'r')]

ix :: Monoid i => Semiring i => Traversal s t a b -> Ixtraversal i s t a b Source #

Index a traversal with a Semiring.

>>> ilists (ix traversed . ix traversed) ["foo", "bar"]
[((),'f'),((),'o'),((),'o'),((),'b'),((),'a'),((),'r')]
>>> ilists (ix @Int traversed . ix traversed) ["foo", "bar"]
[(0,'f'),(1,'o'),(2,'o'),(0,'b'),(1,'a'),(2,'r')]
>>> ilists (ix @[()] traversed . ix traversed) ["foo", "bar"]
[([],'f'),([()],'o'),([(),()],'o'),([],'b'),([()],'a'),([(),()],'r')]
>>> ilists (ix @[()] traversed % ix traversed) ["foo", "bar"]
[([],'f'),([()],'o'),([(),()],'o'),([()],'b'),([(),()],'a'),([(),(),()],'r')]

Traversal1

type Traversal1 s t a b = forall p. (Strong p, Representable p, Apply (Rep p)) => Optic p s t a b Source #

A Traversal1 processes 1 or more parts of the whole, with Apply interactions.

\( \mathsf{Traversal1}\;S\;A = \exists F : \mathsf{Traversable1}, S \equiv F\,A \)

type Traversal1' s a = Traversal1 s s a a Source #

type Ixtraversal1 i s t a b = forall p. (Strong p, Representable p, Apply (Rep p)) => IndexedOptic p i s t a b Source #

type Ixtraversal1' i s a = Ixtraversal1 i s s a a Source #

traversing1 :: Traversable1 f => (s -> a) -> (s -> b -> t) -> Traversal1 (f s) (f t) a b Source #

Obtain a Traversal by lifting a lens getter and setter into a Traversable functor.

 withLens o traversingtraversed . o

Caution: In order for the generated optic to be well-defined, you must ensure that the input functions constitute a legal lens:

  • sa (sbt s a) ≡ a
  • sbt s (sa s) ≡ s
  • sbt (sbt s a1) a2 ≡ sbt s a2

See Property.

The resulting optic can detect copies of the lens stucture inside any Traversable container. For example:

>>> lists (traversing snd $ \(s,_) b -> (s,b)) [(0,'f'),(1,'o'),(2,'o'),(3,'b'),(4,'a'),(5,'r')]
"foobar"

Compare folding.

traversal1Vl :: (forall f. Apply f => (a -> f b) -> s -> f t) -> Traversal1 s t a b Source #

Obtain a profunctor Traversal1 from a Van Laarhoven Traversal1.

Caution: In order for the generated family to be well-defined, you must ensure that the traversal1 law holds for the input function:

  • fmap (abst f) . abst g ≡ getCompose . abst (Compose . fmap f . g)

See Property.

itraversal1Vl :: (forall f. Apply f => (i -> a -> f b) -> s -> f t) -> Ixtraversal1 i s t a b Source #

Lift an indexed VL traversal into an indexed profunctor traversal.

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

  • iabst (const pure) ≡ pure
  • fmap (iabst $ const f) . (iabst $ const g) ≡ getCompose . iabst (const $ Compose . fmap f . g)

See Property.

Optics

traversed :: Traversable f => Traversal (f a) (f b) a b Source #

TODO: Document

traversed1 :: Traversable1 t => Traversal1 (t a) (t b) a b Source #

Obtain a Traversal1 from a Traversable1 functor.

itraversedRep :: Representable f => Traversable f => Ixtraversal (Rep f) (f a) (f b) a b Source #

TODO: Document

both :: Traversal (a, a) (b, b) a b Source #

TODO: Document

>>> withTraversal both (pure . length) ("hello","world")
(5,5)

both1 :: Traversal1 (a, a) (b, b) a b Source #

TODO: Document

>>> withTraversal1 both1 (pure . NE.length) ('h' :| "ello", 'w' :| "orld")
(5,5)

duplicated :: Traversal a b a b Source #

Duplicate the results of any Moore.

>>> lists (both . duplicated) ("hello","world")
["hello","hello","world","world"]

beside :: Bitraversable r => Traversal s1 t1 a b -> Traversal s2 t2 a b -> Traversal (r s1 s2) (r t1 t2) a b Source #

TODO: Document

bitraversed :: Bitraversable f => Traversal (f a a) (f b b) a b Source #

Traverse both parts of a Bitraversable container with matching types.

>>> withTraversal bitraversed (pure . length) (Right "hello")
Right 5
>>> withTraversal bitraversed (pure . length) ("hello","world")
(5,5)
>>> ("hello","world") ^. bitraversed
"helloworld"
bitraversed :: Traversal (a , a) (b , b) a b
bitraversed :: Traversal (a + a) (b + b) a b

bitraversed1 :: Bitraversable1 r => Traversal1 (r a a) (r b b) a b Source #

Traverse both parts of a Bitraversable1 container with matching types.

>>> withTraversal1 bitraversed1 (pure . NE.length) ('h' :| "ello", 'w' :| "orld")
(5,5)

repeated :: Traversal1' a a Source #

Obtain a Traversal1' by repeating the input forever.

repeatlists repeated
>>> take 5 $ 5 ^.. repeated
[5,5,5,5,5]
repeated :: Fold1 a a

iterated :: (a -> a) -> Traversal1' a a Source #

x ^. iterated f returns an infinite Traversal1' of repeated applications of f to x.

lists (iterated f) a ≡ iterate f a
>>> take 3 $ (1 :: Int) ^.. iterated (+1)
[1,2,3]
iterated :: (a -> a) -> Fold1 a a

cycled :: Apply f => ATraversal1' f s a -> ATraversal1' f s a Source #

Transform a Traversal1' into a Traversal1' that loops over its elements repeatedly.

>>> take 7 $ (1 :| [2,3]) ^.. cycled traversed1
[1,2,3,1,2,3,1]
cycled :: Fold1 s a -> Fold1 s a

Operators

withTraversal :: Applicative f => ATraversal f s t a b -> (a -> f b) -> s -> f t Source #

The traversal laws can be stated in terms of withTraversal:

  • withTraversal t (Identity . f) ≡ Identity (fmap f)
  • Compose . fmap (withTraversal t f) . withTraversal t g ≡ withTraversal t (Compose . fmap f . g)

withTraversal1 :: Apply f => ATraversal1 f s t a b -> (a -> f b) -> s -> f t Source #

The traversal laws can be stated in terms of withTraversal1:

  • withTraversal1 t (Identity . f) ≡  Identity (fmap f)
  • Compose . fmap (withTraversal1 t f) . withTraversal1 t g ≡ withTraversal1 t (Compose . fmap f . g)
withTraversal1 :: Functor f => Lens s t a b -> (a -> f b) -> s -> f t
withTraversal1 :: Apply f => Traversal1 s t a b -> (a -> f b) -> s -> f t

Operators

(*~) :: Optic (Star f) s t a b -> f b -> s -> f t infixr 4 Source #

Set the focus of a representable optic.

(**~) :: Optic (Star f) s t a b -> (a -> f b) -> s -> f t infixr 4 Source #

Map over a representable optic.

sequences :: Applicative f => ATraversal f s t (f a) a -> s -> f t Source #

TODO: Document

sequences1 :: Apply f => ATraversal1 f s t (f a) a -> s -> f t Source #

TODO: Document