Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Traversal1 s t a b = forall (p :: Type -> Type -> Type). IsTraversal1 p => Optic p s t a b
- type Traversal1' s a = Traversal1 s s a a
- class (IsLens p, Traversing1 p) => IsTraversal1 (p :: Type -> Type -> Type)
- traversal1 :: (forall (f :: Type -> Type). Apply f => (a -> f b) -> s -> f t) -> Traversal1 s t a b
- traversed1 :: forall (t :: Type -> Type) a b. Traversable1 t => Traversal1 (t a) (t b) a b
- backwards :: Traversal1 s t a b -> Traversal1 s t a b
- both :: forall (r :: Type -> Type -> Type) a b. Bitraversable1 r => Traversal1 (r a a) (r b b) a b
- beside :: forall (r :: Type -> Type -> Type) s1 t1 a b s2 t2. Bitraversable1 r => Traversal1 s1 t1 a b -> Traversal1 s2 t2 a b -> Traversal1 (r s1 s2) (r t1 t2) a b
- traverse1Of :: Apply f => Traversal1 s t a b -> (a -> f b) -> s -> f t
- for1Of :: Apply f => Traversal1 s t a b -> s -> (a -> f b) -> f t
- sequence1Of :: Apply f => Traversal1 s t (f b) b -> s -> f t
- transposeOf :: Traversal1 s t (NonEmpty a) a -> s -> NonEmpty t
Relevant traversals
type Traversal1 s t a b = forall (p :: Type -> Type -> Type). IsTraversal1 p => Optic p s t a b Source #
type Traversal1' s a = Traversal1 s s a a Source #
class (IsLens p, Traversing1 p) => IsTraversal1 (p :: Type -> Type -> Type) Source #
Instances
Apply f => IsTraversal1 (OptionalStar f) Source # | |
Defined in Fresnel.Traversal1.Internal | |
Apply f => IsTraversal1 (Star1 f) Source # | |
Defined in Fresnel.Traversal1.Internal | |
Monad m => IsTraversal1 (Kleisli m) Source # | |
Defined in Fresnel.Traversal1.Internal | |
Semigroup r => IsTraversal1 (Forget r :: Type -> Type -> Type) Source # | |
Defined in Fresnel.Traversal1.Internal | |
Applicative f => IsTraversal1 (Star f) Source # | |
Defined in Fresnel.Traversal1.Internal | |
IsTraversal1 (->) Source # | |
Defined in Fresnel.Traversal1.Internal |
Construction
traversal1 :: (forall (f :: Type -> Type). Apply f => (a -> f b) -> s -> f t) -> Traversal1 s t a b Source #
traversed1 :: forall (t :: Type -> Type) a b. Traversable1 t => Traversal1 (t a) (t b) a b Source #
backwards :: Traversal1 s t a b -> Traversal1 s t a b Source #
Reverse the order in which a (finite) Traversal1
is traversed.
backwards
.backwards
=id
both :: forall (r :: Type -> Type -> Type) a b. Bitraversable1 r => Traversal1 (r a a) (r b b) a b Source #
beside :: forall (r :: Type -> Type -> Type) s1 t1 a b s2 t2. Bitraversable1 r => Traversal1 s1 t1 a b -> Traversal1 s2 t2 a b -> Traversal1 (r s1 s2) (r t1 t2) a b Source #
Elimination
traverse1Of :: Apply f => Traversal1 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.
traverse1Of
.traversal1
=id
traverse1Of
traversed1
=traverse1
for1Of :: Apply f => Traversal1 s t a b -> s -> (a -> f b) -> f t Source #
sequence1Of :: Apply f => Traversal1 s t (f b) b -> s -> f t Source #
transposeOf :: Traversal1 s t (NonEmpty a) a -> s -> NonEmpty t Source #