Copyright | (c) Justin Le 2019 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- class HFunctor t => HTraversable t where
- htraverse :: Applicative h => (forall x. f x -> h (g x)) -> t f a -> h (t g a)
- hsequence :: (HTraversable t, Applicative h) => t (h :.: f) a -> h (t f a)
- hfoldMap :: (HTraversable t, Monoid m) => (forall x. f x -> m) -> t f a -> m
- htoList :: HTraversable t => (forall x. f x -> b) -> t f a -> [b]
- hmapDefault :: HTraversable t => (f ~> g) -> t f ~> t g
- hfor :: (HTraversable t, Applicative h) => t f a -> (forall x. f x -> h (g x)) -> h (t g a)
- class HTraversable t => HTraversable1 t where
- htraverse1 :: Apply h => (forall x. f x -> h (g x)) -> t f a -> h (t g a)
- hsequence1 :: (HTraversable1 t, Apply h) => t (h :.: f) a -> h (t f a)
- hfoldMap1 :: (HTraversable1 t, Semigroup m) => (forall x. f x -> m) -> t f a -> m
- htoNonEmpty :: HTraversable1 t => (forall x. f x -> b) -> t f a -> NonEmpty b
- hfor1 :: (HTraversable1 t, Apply h) => t f a -> (forall x. f x -> h (g x)) -> h (t g a)
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
htraverse :: Applicative h => (forall x. f x -> h (g x)) -> t f a -> h (t g a) Source #
Instances
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 x
s 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 x
s 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 #
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
htraverse1 :: Apply h => (forall x. f x -> h (g x)) -> t f a -> h (t g a) Source #
Instances
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 x
s 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 x
s 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