ten-0.1.0.2: Typeclasses like Functor, etc. over arity-1 type constructors.
Safe HaskellNone
LanguageHaskell2010

Data.Ten.Traversable

Description

Provides an analog of Traversable over arity-1 type constructors.

Synopsis

Documentation

class (Functor10 t, Foldable10 t) => Traversable10 (t :: (k -> Type) -> Type) where Source #

Analog of Traversable over arity-1 type constructors.

This is defined in terms of mapTraverse10 for two reasons:

Methods

mapTraverse10 :: forall f m n r. Applicative f => (t n -> r) -> (forall a. m a -> f (n a)) -> t m -> f r Source #

traverse10 with a built-in fmap on the final result.

Instances

Instances details
Traversable10 (U1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Traversable

Methods

mapTraverse10 :: forall f m n r. Applicative f => (U1 n -> r) -> (forall (a :: k0). m a -> f (n a)) -> U1 m -> f r Source #

Traversable10 (V1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Traversable

Methods

mapTraverse10 :: forall f m n r. Applicative f => (V1 n -> r) -> (forall (a :: k0). m a -> f (n a)) -> V1 m -> f r Source #

Traversable10 (Exists :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Exists

Methods

mapTraverse10 :: forall f m n r. Applicative f => (Exists n -> r) -> (forall (a :: k0). m a -> f (n a)) -> Exists m -> f r Source #

Traversable10 f => Traversable10 (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Traversable

Methods

mapTraverse10 :: forall f0 m n r. Applicative f0 => (Rec1 f n -> r) -> (forall (a :: k0). m a -> f0 (n a)) -> Rec1 f m -> f0 r Source #

Traversable10 (Ap10 a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Traversable

Methods

mapTraverse10 :: forall f m n r. Applicative f => (Ap10 a n -> r) -> (forall (a0 :: k0). m a0 -> f (n a0)) -> Ap10 a m -> f r Source #

(Traversable10 f, Traversable10 g) => Traversable10 (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Traversable

Methods

mapTraverse10 :: forall f0 m n r. Applicative f0 => ((f :*: g) n -> r) -> (forall (a :: k0). m a -> f0 (n a)) -> (f :*: g) m -> f0 r Source #

(Traversable10 f, Traversable10 g) => Traversable10 (f :+: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Traversable

Methods

mapTraverse10 :: forall f0 m n r. Applicative f0 => ((f :+: g) n -> r) -> (forall (a :: k0). m a -> f0 (n a)) -> (f :+: g) m -> f0 r Source #

Traversable10 (K1 i a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Traversable

Methods

mapTraverse10 :: forall f m n r. Applicative f => (K1 i a n -> r) -> (forall (a0 :: k0). m a0 -> f (n a0)) -> K1 i a m -> f r Source #

(Generic1 f, Traversable10 (Rep1 f)) => Traversable10 (Wrapped1 (Generic1 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Traversable

Methods

mapTraverse10 :: forall f0 m n r. Applicative f0 => (Wrapped1 Generic1 f n -> r) -> (forall (a :: k0). m a -> f0 (n a)) -> Wrapped1 Generic1 f m -> f0 r Source #

Traversable10 f => Traversable10 (Wrapped1 (Representable10 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) Source #

Superclass appeasement; deriving via this will give infinite loops; don't!

Instance details

Defined in Data.Ten.Representable

Methods

mapTraverse10 :: forall f0 m n r. Applicative f0 => (Wrapped1 Representable10 f n -> r) -> (forall (a :: k0). m a -> f0 (n a)) -> Wrapped1 Representable10 f m -> f0 r Source #

(Traversable f, Traversable10 g) => Traversable10 (f :.: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Traversable

Methods

mapTraverse10 :: forall f0 m n r. Applicative f0 => ((f :.: g) n -> r) -> (forall (a :: k0). m a -> f0 (n a)) -> (f :.: g) m -> f0 r Source #

Traversable10 f => Traversable10 (M1 i c f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Traversable

Methods

mapTraverse10 :: forall f0 m n r. Applicative f0 => (M1 i c f n -> r) -> (forall (a :: k0). m a -> f0 (n a)) -> M1 i c f m -> f0 r Source #

Traversable10 ((:**) k :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Sigma

Methods

mapTraverse10 :: forall f m n r. Applicative f => ((k :** n) -> r) -> (forall (a :: k0). m a -> f (n a)) -> (k :** m) -> f r Source #

traverse10 :: forall t f m n. (Traversable10 t, Applicative f) => (forall a. m a -> f (n a)) -> t m -> f (t n) Source #

Analog of traverse for functors over arity-1 type constructors.

Given a parametric function that takes the wrapped type m a to n a in an Applicative f, visit all contained m _s to convert from t m to t n.

m and n here play the role of a and b in the normal traverse type; that is, instead of traversing to change a Type, we're traversing to change a type constructor of kind k -> Type:

    traverse
      :: (Traversable t, Applicative f)
      => (          a   -> f  b   ) -> t a -> f (t b)
    traverse10
      :: (Traversable10 t, Applicative f)
      => (forall x. m x -> f (n x)) -> t m -> f (t n)

sequenceA10 :: (Applicative m, Traversable10 f) => f m -> m (f Identity) Source #

sequenceA for Traversable10.

This variant expects just the plain m actions at each field, and wraps the results in @Identity.

fsequenceA10 :: (Applicative m, Traversable10 f) => f (m :.: n) -> m (f n) Source #

sequenceA for Traversable10.

This variant expects the composition of the Applicative being sequenced with some inner type constructor at each field.