functor-combinators-0.4.1.2: Tools for functor combinator-based program design
Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.HFunctor.HTraversable

Description

Provides a "higher-order" version of Traversable and Traversable1, in the same way that HFunctor is a higher-order version of Functor.

Note that in theory we could have HFoldable as well, in the hierarchy, to represent something that does not have an HFunctor instance. But it is not clear exactly why it would be useful as an abstraction. This may be added in the future if use cases pop up. For the most part, the things you would want to do with an HFoldable, you could do with hfoldMap or iget; it could in theory be useful for things without HTraversable or Interpret instances, but it isn't clear what those instances might be.

For instances of Interpret, there is some overlap with the functionality of iget, icollect, and icollect1.

Since: 0.3.6.0

Synopsis

HTraversable

class HFunctor t => HTraversable t where Source #

A higher-kinded version of Traversable, in the same way that HFunctor is the higher-kinded version of Functor. Gives you an "effectful" hmap, in the same way that traverse gives you an effectful fmap.

The typical analogues of Traversable laws apply.

Since: 0.3.6.0

Methods

htraverse :: Applicative h => (forall x. f x -> h (g x)) -> t f a -> h (t g a) Source #

An "effectful" hmap, in the same way that traverse is an effectful fmap.

Instances

Instances details
HTraversable Ap Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Ap f a -> h (Ap g a) Source #

HTraversable Ap Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Ap f a -> h (Ap g a) Source #

HTraversable Ap1 Source # 
Instance details

Defined in Data.Functor.Apply.Free

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Ap1 f a -> h (Ap1 g a) Source #

HTraversable Dec Source # 
Instance details

Defined in Data.Functor.Contravariant.Divisible.Free

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Dec f a -> h (Dec g a) Source #

HTraversable Dec1 Source # 
Instance details

Defined in Data.Functor.Contravariant.Divisible.Free

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Dec1 f a -> h (Dec1 g a) Source #

HTraversable Div Source # 
Instance details

Defined in Data.Functor.Contravariant.Divisible.Free

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Div f a -> h (Div g a) Source #

HTraversable Div1 Source # 
Instance details

Defined in Data.Functor.Contravariant.Divisible.Free

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Div1 f a -> h (Div1 g a) Source #

HTraversable DecAlt Source # 
Instance details

Defined in Data.HFunctor.Chain.Internal

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> DecAlt f a -> h (DecAlt g a) Source #

HTraversable DecAlt1 Source # 
Instance details

Defined in Data.HFunctor.Chain.Internal

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> DecAlt1 f a -> h (DecAlt1 g a) Source #

HTraversable Coyoneda Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Coyoneda f a -> h (Coyoneda g a) Source #

HTraversable Coyoneda Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Coyoneda f a -> h (Coyoneda g a) Source #

HTraversable MaybeApply Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> MaybeApply f a -> h (MaybeApply g a) Source #

HTraversable WrappedApplicative Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> WrappedApplicative f a -> h (WrappedApplicative g a) Source #

HTraversable Lift Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Lift f a -> h (Lift g a) Source #

HTraversable MaybeT Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> MaybeT f a -> h (MaybeT g a) Source #

HTraversable (EnvT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> EnvT e f a -> h (EnvT e g a) Source #

HTraversable (Night f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f0 g (a :: k1). Applicative h => (forall (x :: k). f0 x -> h (g x)) -> Night f f0 a -> h (Night f g a) Source #

HTraversable (Post a :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.Route

Methods

htraverse :: forall h f g (a0 :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Post a f a0 -> h (Post a g a0) Source #

HTraversable t => HTraversable (PostT t :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.Route

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> PostT t f a -> h (PostT t g a) Source #

HTraversable (Pre a :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.Route

Methods

htraverse :: forall h f g (a0 :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Pre a f a0 -> h (Pre a g a0) Source #

HTraversable t => HTraversable (PreT t :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.Route

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> PreT t f a -> h (PreT t g a) Source #

HTraversable (Day f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f0 g (a :: k1). Applicative h => (forall (x :: k). f0 x -> h (g x)) -> Day f f0 a -> h (Day f g a) Source #

HTraversable (These1 f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f0 g (a :: k1). Applicative h => (forall (x :: k). f0 x -> h (g x)) -> These1 f f0 a -> h (These1 f g a) Source #

HTraversable (Tagged :: (k -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k0). f x -> h (g x)) -> Tagged f a -> h (Tagged g a) Source #

HTraversable (ListF :: (k1 -> Type) -> k1 -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k). f x -> h (g x)) -> ListF f a -> h (ListF g a) Source #

HTraversable (MaybeF :: (k1 -> Type) -> k1 -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k). f x -> h (g x)) -> MaybeF f a -> h (MaybeF g a) Source #

HTraversable (NonEmptyF :: (k1 -> Type) -> k1 -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k). f x -> h (g x)) -> NonEmptyF f a -> h (NonEmptyF g a) Source #

HTraversable (Flagged :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k). f x -> h (g x)) -> Flagged f a -> h (Flagged g a) Source #

HTraversable (Step :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k). f x -> h (g x)) -> Step f a -> h (Step g a) Source #

HTraversable (Steps :: (k1 -> TYPE LiftedRep) -> k1 -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k). f x -> h (g x)) -> Steps f a -> h (Steps g a) Source #

HTraversable (Backwards :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k). f x -> h (g x)) -> Backwards f a -> h (Backwards g a) Source #

HTraversable (IdentityT :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k). f x -> h (g x)) -> IdentityT f a -> h (IdentityT g a) Source #

HTraversable (Reverse :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k). f x -> h (g x)) -> Reverse f a -> h (Reverse g a) Source #

(HTraversable s, HTraversable t) => HTraversable (ComposeT s t :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> ComposeT s t f a -> h (ComposeT s t g a) Source #

HTraversable (Void2 :: (k -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k0). f x -> h (g x)) -> Void2 f a -> h (Void2 g a) Source #

HTraversable (ProxyF :: (k -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k0). f x -> h (g x)) -> ProxyF f a -> h (ProxyF g a) Source #

HTraversable (Product f :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f0 g (a :: k10). Applicative h => (forall (x :: k). f0 x -> h (g x)) -> Product f f0 a -> h (Product f g a) Source #

HTraversable (Sum f :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f0 g (a :: k10). Applicative h => (forall (x :: k). f0 x -> h (g x)) -> Sum f f0 a -> h (Sum f g a) Source #

HTraversable ((:*:) f :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f0 g (a :: k10). Applicative h => (forall (x :: k). f0 x -> h (g x)) -> (f :*: f0) a -> h ((f :*: g) a) Source #

HTraversable ((:+:) f :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f0 g (a :: k10). Applicative h => (forall (x :: k). f0 x -> h (g x)) -> (f :+: f0) a -> h ((f :+: g) a) Source #

HTraversable (MapF k :: (k1 -> Type) -> k1 -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k0). f x -> h (g x)) -> MapF k f a -> h (MapF k g a) Source #

HTraversable (NEMapF k :: (k1 -> TYPE LiftedRep) -> k1 -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k0). f x -> h (g x)) -> NEMapF k f a -> h (NEMapF k g a) Source #

HTraversable t => HTraversable (HFree t :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k). f x -> h (g x)) -> HFree t f a -> h (HFree t g a) Source #

HTraversable t => HTraversable (HLift t :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k). f x -> h (g x)) -> HLift t f a -> h (HLift t g a) Source #

HTraversable (Joker f :: (k -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f0 g (a :: k10). Applicative h => (forall (x :: k0). f0 x -> h (g x)) -> Joker f f0 a -> h (Joker f g a) Source #

HTraversable (LeftF f :: (k -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HBifunctor

Methods

htraverse :: forall h f0 g (a :: k10). Applicative h => (forall (x :: k0). f0 x -> h (g x)) -> LeftF f f0 a -> h (LeftF f g a) Source #

HTraversable (ConstF e :: (k -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k0). f x -> h (g x)) -> ConstF e f a -> h (ConstF e g a) Source #

Traversable f => HTraversable ((:.:) f :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f0 g (a :: k10). Applicative h => (forall (x :: k). f0 x -> h (g x)) -> (f :.: f0) a -> h ((f :.: g) a) Source #

HTraversable (M1 i c :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k10). Applicative h => (forall (x :: k). f x -> h (g x)) -> M1 i c f a -> h (M1 i c g a) Source #

HTraversable (RightF g :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HBifunctor

Methods

htraverse :: forall h f g0 (a :: k10). Applicative h => (forall (x :: k). f x -> h (g0 x)) -> RightF g f a -> h (RightF g g0 a) Source #

HTraversable (Void3 f :: (k2 -> Type) -> k3 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f0 g (a :: k1). Applicative h => (forall (x :: k). f0 x -> h (g x)) -> Void3 f f0 a -> h (Void3 f g a) Source #

HTraversable Alt Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Alt f a -> h (Alt g a) Source #

HTraversable AltF Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> AltF f a -> h (AltF g a) Source #

HTraversable Ap Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> Ap f a -> h (Ap g a) Source #

HTraversable (NP :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k0). f x -> h (g x)) -> NP f a -> h (NP g a) Source #

HTraversable (NS :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k0). f x -> h (g x)) -> NS f a -> h (NS g a) Source #

HTraversable (CoRec :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k0). f x -> h (g x)) -> CoRec f a -> h (CoRec g a) Source #

HTraversable (Rec :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k0). f x -> h (g x)) -> Rec f a -> h (Rec g a) Source #

HTraversable (Day f :: (TYPE LiftedRep -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse :: forall h f0 g (a :: k1). Applicative h => (forall (x :: k). f0 x -> h (g x)) -> Day f f0 a -> h (Day f g a) Source #

HTraversable DivAp Source # 
Instance details

Defined in Data.HFunctor.Chain.Internal

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> DivAp f a -> h (DivAp g a) Source #

HTraversable DivAp1 Source # 
Instance details

Defined in Data.HFunctor.Chain.Internal

Methods

htraverse :: forall h f g (a :: k1). Applicative h => (forall (x :: k). f x -> h (g x)) -> DivAp1 f a -> h (DivAp1 g a) Source #

hsequence :: (HTraversable t, Applicative h) => t (h :.: f) a -> h (t f a) Source #

A wrapper over a common pattern of "inverting" layers of a functor combinator.

Since: 0.3.6.0

hfoldMap :: (HTraversable t, Monoid m) => (forall x. f x -> m) -> t f a -> m Source #

Collect all the f xs inside a t f a into a monoidal result using a projecting function.

See iget.

Since: 0.3.6.0

htoList :: HTraversable t => (forall x. f x -> b) -> t f a -> [b] Source #

Collect all the f xs inside a t f a into a list, using a projecting function.

See icollect.

Since: 0.3.6.0

hmapDefault :: HTraversable t => (f ~> g) -> t f ~> t g Source #

An implementation of hmap defined using htraverse.

Since: 0.3.6.0

hfor :: (HTraversable t, Applicative h) => t f a -> (forall x. f x -> h (g x)) -> h (t g a) Source #

A flipped version of htraverse.

Since: 0.4.0.0

HTraversable1

class HTraversable t => HTraversable1 t where Source #

A higher-kinded version of Traversable1, in the same way that HFunctor is the higher-kinded version of Functor. Gives you an "effectful" hmap, in the same way that traverse1 gives you an effectful fmap, guaranteeing at least one item.

The typical analogues of Traversable1 laws apply.

Since: 0.3.6.0

Methods

htraverse1 :: Apply h => (forall x. f x -> h (g x)) -> t f a -> h (t g a) Source #

An "effectful" hmap, in the same way that traverse1 is an effectful fmap, guaranteeing at least one item.

Instances

Instances details
HTraversable1 Ap1 Source # 
Instance details

Defined in Data.Functor.Apply.Free

Methods

htraverse1 :: forall h f g (a :: k1). Apply h => (forall (x :: k). f x -> h (g x)) -> Ap1 f a -> h (Ap1 g a) Source #

HTraversable1 Dec1 Source # 
Instance details

Defined in Data.Functor.Contravariant.Divisible.Free

Methods

htraverse1 :: forall h f g (a :: k1). Apply h => (forall (x :: k). f x -> h (g x)) -> Dec1 f a -> h (Dec1 g a) Source #

HTraversable1 Div1 Source # 
Instance details

Defined in Data.Functor.Contravariant.Divisible.Free

Methods

htraverse1 :: forall h f g (a :: k1). Apply h => (forall (x :: k). f x -> h (g x)) -> Div1 f a -> h (Div1 g a) Source #

HTraversable1 DecAlt1 Source # 
Instance details

Defined in Data.HFunctor.Chain.Internal

Methods

htraverse1 :: forall h f g (a :: k1). Apply h => (forall (x :: k). f x -> h (g x)) -> DecAlt1 f a -> h (DecAlt1 g a) Source #

HTraversable1 Coyoneda Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k1). Apply h => (forall (x :: k). f x -> h (g x)) -> Coyoneda f a -> h (Coyoneda g a) Source #

HTraversable1 Coyoneda Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k1). Apply h => (forall (x :: k). f x -> h (g x)) -> Coyoneda f a -> h (Coyoneda g a) Source #

HTraversable1 MaybeT Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k1). Apply h => (forall (x :: k). f x -> h (g x)) -> MaybeT f a -> h (MaybeT g a) Source #

HTraversable1 (EnvT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k1). Apply h => (forall (x :: k). f x -> h (g x)) -> EnvT e f a -> h (EnvT e g a) Source #

HTraversable1 (Night f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f0 g (a :: k1). Apply h => (forall (x :: k). f0 x -> h (g x)) -> Night f f0 a -> h (Night f g a) Source #

HTraversable1 (Day f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f0 g (a :: k1). Apply h => (forall (x :: k). f0 x -> h (g x)) -> Day f f0 a -> h (Day f g a) Source #

HTraversable1 (NonEmptyF :: (k1 -> Type) -> k1 -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k10). Apply h => (forall (x :: k). f x -> h (g x)) -> NonEmptyF f a -> h (NonEmptyF g a) Source #

HTraversable1 (Flagged :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k10). Apply h => (forall (x :: k). f x -> h (g x)) -> Flagged f a -> h (Flagged g a) Source #

HTraversable1 (Step :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k10). Apply h => (forall (x :: k). f x -> h (g x)) -> Step f a -> h (Step g a) Source #

HTraversable1 (Steps :: (k1 -> TYPE LiftedRep) -> k1 -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k10). Apply h => (forall (x :: k). f x -> h (g x)) -> Steps f a -> h (Steps g a) Source #

HTraversable1 (IdentityT :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k10). Apply h => (forall (x :: k). f x -> h (g x)) -> IdentityT f a -> h (IdentityT g a) Source #

HTraversable1 (Reverse :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k10). Apply h => (forall (x :: k). f x -> h (g x)) -> Reverse f a -> h (Reverse g a) Source #

HTraversable1 (Void2 :: (k -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k10). Apply h => (forall (x :: k0). f x -> h (g x)) -> Void2 f a -> h (Void2 g a) Source #

HTraversable1 (Product f :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f0 g (a :: k10). Apply h => (forall (x :: k). f0 x -> h (g x)) -> Product f f0 a -> h (Product f g a) Source #

HTraversable1 ((:*:) f :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f0 g (a :: k10). Apply h => (forall (x :: k). f0 x -> h (g x)) -> (f :*: f0) a -> h ((f :*: g) a) Source #

HTraversable1 (NEMapF k :: (k1 -> TYPE LiftedRep) -> k1 -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k10). Apply h => (forall (x :: k0). f x -> h (g x)) -> NEMapF k f a -> h (NEMapF k g a) Source #

HTraversable1 t => HTraversable1 (HFree t :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k10). Apply h => (forall (x :: k). f x -> h (g x)) -> HFree t f a -> h (HFree t g a) Source #

HTraversable1 t => HTraversable1 (HLift t :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k10). Apply h => (forall (x :: k). f x -> h (g x)) -> HLift t f a -> h (HLift t g a) Source #

Traversable1 f => HTraversable1 ((:.:) f :: (k1 -> TYPE LiftedRep) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f0 g (a :: k10). Apply h => (forall (x :: k). f0 x -> h (g x)) -> (f :.: f0) a -> h ((f :.: g) a) Source #

HTraversable1 (M1 i c :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k10). Apply h => (forall (x :: k). f x -> h (g x)) -> M1 i c f a -> h (M1 i c g a) Source #

HTraversable1 (NS :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f g (a :: k1). Apply h => (forall (x :: k0). f x -> h (g x)) -> NS f a -> h (NS g a) Source #

HTraversable1 (Day f :: (TYPE LiftedRep -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.HTraversable

Methods

htraverse1 :: forall h f0 g (a :: k1). Apply h => (forall (x :: k). f0 x -> h (g x)) -> Day f f0 a -> h (Day f g a) Source #

HTraversable1 DivAp1 Source # 
Instance details

Defined in Data.HFunctor.Chain.Internal

Methods

htraverse1 :: forall h f g (a :: k1). Apply h => (forall (x :: k). f x -> h (g x)) -> DivAp1 f a -> h (DivAp1 g a) Source #

hsequence1 :: (HTraversable1 t, Apply h) => t (h :.: f) a -> h (t f a) Source #

A wrapper over a common pattern of "inverting" layers of a functor combinator that always contains at least one f item.

Since: 0.3.6.0

hfoldMap1 :: (HTraversable1 t, Semigroup m) => (forall x. f x -> m) -> t f a -> m Source #

Collect all the f xs inside a t f a into a semigroupoidal result using a projecting function.

See iget.

Since: 0.3.6.0

htoNonEmpty :: HTraversable1 t => (forall x. f x -> b) -> t f a -> NonEmpty b Source #

Collect all the f xs inside a t f a into a non-empty list, using a projecting function.

See icollect1.

Since: 0.3.6.0

hfor1 :: (HTraversable1 t, Apply h) => t f a -> (forall x. f x -> h (g x)) -> h (t g a) Source #

A flipped version of htraverse1.

Since: 0.4.0.0