fresnel-0.1.0.1: high-powered optics in a small package
Safe HaskellNone
LanguageHaskell2010

Fresnel.Traversal

Synopsis

Traversals

type Traversal s t a b = forall (p :: Type -> Type -> Type). IsTraversal p => Optic p s t a b Source #

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

class (IsOptional p, IsTraversal1 p, Traversing p) => IsTraversal (p :: Type -> Type -> Type) Source #

Instances

Instances details
Monad m => IsTraversal (Kleisli m) Source # 
Instance details

Defined in Fresnel.Traversal.Internal

Monoid r => IsTraversal (Forget r :: Type -> Type -> Type) Source # 
Instance details

Defined in Fresnel.Traversal.Internal

Applicative f => IsTraversal (Star f) Source # 
Instance details

Defined in Fresnel.Traversal.Internal

IsTraversal (->) Source # 
Instance details

Defined in Fresnel.Traversal.Internal

Construction

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

traversed :: forall (t :: Type -> Type) a b. Traversable t => Traversal (t a) (t b) a b Source #

backwards :: Traversal s t a b -> Traversal s t a b Source #

Reverse the order in which a (finite) Traversal is traversed.

backwards . backwards = id

both :: forall (r :: Type -> Type -> Type) a b. Bitraversable r => Traversal (r a a) (r b b) a b Source #

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

ignored :: forall s a b p. IsTraversal p => Optic p s s a b Source #

The trivially empty Traversal.

traverseOf ignored f = pure

Elimination

traverseOf :: Applicative f => Traversal s t a b -> (a -> f b) -> s -> f t Source #

Map over the targets of an Iso, Lens, Optional, or Traversal, collecting the results.

traverseOf . traversal = id
traverseOf traversed = traverse

forOf :: Applicative f => Traversal s t a b -> s -> (a -> f b) -> f t Source #

sequenceOf :: Applicative f => Traversal s t (f b) b -> s -> f t Source #

transposeOf :: Traversal s t [a] a -> s -> [t] Source #

mapAccumLOf :: Traversal s t a b -> (accum -> a -> (b, accum)) -> accum -> s -> (t, accum) Source #

mapAccumROf :: Traversal s t a b -> (accum -> a -> (b, accum)) -> accum -> s -> (t, accum) Source #

scanl1Of :: Traversal s t a a -> (a -> a -> a) -> s -> t Source #

scanr1Of :: Traversal s t a a -> (a -> a -> a) -> s -> t Source #