semigroupoids-5.2.2: Semigroupoids: Category sans id

Copyright(C) 2011-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Data.Semigroup.Traversable

Description

 

Documentation

class (Foldable1 t, Traversable t) => Traversable1 t where Source #

Minimal complete definition

traverse1 | sequence1

Methods

traverse1 :: Apply f => (a -> f b) -> t a -> f (t b) Source #

sequence1 :: Apply f => t (f b) -> f (t b) Source #

Instances

Traversable1 Par1 Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Par1 a -> f (Par1 b) Source #

sequence1 :: Apply f => Par1 (f b) -> f (Par1 b) Source #

Traversable1 Complex Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Complex a -> f (Complex b) Source #

sequence1 :: Apply f => Complex (f b) -> f (Complex b) Source #

Traversable1 NonEmpty Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> NonEmpty a -> f (NonEmpty b) Source #

sequence1 :: Apply f => NonEmpty (f b) -> f (NonEmpty b) Source #

Traversable1 Identity Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Identity a -> f (Identity b) Source #

sequence1 :: Apply f => Identity (f b) -> f (Identity b) Source #

Traversable1 Tree Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Tree a -> f (Tree b) Source #

sequence1 :: Apply f => Tree (f b) -> f (Tree b) Source #

Traversable1 (V1 *) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> V1 * a -> f (V1 * b) Source #

sequence1 :: Apply f => V1 * (f b) -> f (V1 * b) Source #

Traversable1 ((,) a) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> (a, a) -> f (a, b) Source #

sequence1 :: Apply f => (a, f b) -> f (a, b) Source #

Traversable1 f => Traversable1 (Lift f) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Lift f a -> f (Lift f b) Source #

sequence1 :: Apply f => Lift f (f b) -> f (Lift f b) Source #

Traversable1 f => Traversable1 (Rec1 * f) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Rec1 * f a -> f (Rec1 * f b) Source #

sequence1 :: Apply f => Rec1 * f (f b) -> f (Rec1 * f b) Source #

Bitraversable1 p => Traversable1 (Join * p) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Join * p a -> f (Join * p b) Source #

sequence1 :: Apply f => Join * p (f b) -> f (Join * p b) Source #

Traversable1 f => Traversable1 (IdentityT * f) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> IdentityT * f a -> f (IdentityT * f b) Source #

sequence1 :: Apply f => IdentityT * f (f b) -> f (IdentityT * f b) Source #

Traversable1 (Tagged * a) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Tagged * a a -> f (Tagged * a b) Source #

sequence1 :: Apply f => Tagged * a (f b) -> f (Tagged * a b) Source #

Traversable1 f => Traversable1 (Reverse * f) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Reverse * f a -> f (Reverse * f b) Source #

sequence1 :: Apply f => Reverse * f (f b) -> f (Reverse * f b) Source #

Traversable1 f => Traversable1 (Backwards * f) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Backwards * f a -> f (Backwards * f b) Source #

sequence1 :: Apply f => Backwards * f (f b) -> f (Backwards * f b) Source #

(Traversable1 f, Traversable1 g) => Traversable1 ((:+:) * f g) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> (* :+: f) g a -> f ((* :+: f) g b) Source #

sequence1 :: Apply f => (* :+: f) g (f b) -> f ((* :+: f) g b) Source #

(Traversable1 f, Traversable1 g) => Traversable1 ((:*:) * f g) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> (* :*: f) g a -> f ((* :*: f) g b) Source #

sequence1 :: Apply f => (* :*: f) g (f b) -> f ((* :*: f) g b) Source #

(Traversable1 f, Traversable1 g) => Traversable1 (Product * f g) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Product * f g a -> f (Product * f g b) Source #

sequence1 :: Apply f => Product * f g (f b) -> f (Product * f g b) Source #

(Traversable1 f, Traversable1 g) => Traversable1 (Sum * f g) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Sum * f g a -> f (Sum * f g b) Source #

sequence1 :: Apply f => Sum * f g (f b) -> f (Sum * f g b) Source #

Traversable1 f => Traversable1 (M1 * i c f) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> M1 * i c f a -> f (M1 * i c f b) Source #

sequence1 :: Apply f => M1 * i c f (f b) -> f (M1 * i c f b) Source #

(Traversable1 f, Traversable1 g) => Traversable1 ((:.:) * * f g) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> (* :.: *) f g a -> f ((* :.: *) f g b) Source #

sequence1 :: Apply f => (* :.: *) f g (f b) -> f ((* :.: *) f g b) Source #

(Traversable1 f, Traversable1 g) => Traversable1 (Compose * * f g) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Compose * * f g a -> f (Compose * * f g b) Source #

sequence1 :: Apply f => Compose * * f g (f b) -> f (Compose * * f g b) Source #

Traversable1 g => Traversable1 (Joker * * g a) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Joker * * g a a -> f (Joker * * g a b) Source #

sequence1 :: Apply f => Joker * * g a (f b) -> f (Joker * * g a b) Source #

foldMap1Default :: (Traversable1 f, Semigroup m) => (a -> m) -> f a -> m Source #