Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Generic implementation of Foldable
and Traversable
.
There is already a naive implementation using the generic
's
own instances of Rep
Foldable
and Traversable
. However, deriving then
generates a lot of code that may not be simplified away by GHC,
that results in unnecessary run-time overhead.
In contrast, this implementation guarantees that the generated code is
identical to stock-derived instances of Foldable
and Traversable
,
which have the following syntactic properties:
- constructors with zero fields use
pure
once; - constructors with one field use
fmap
once; - constructors with n >= 2 fields use
liftA2
once and(
n-2 times.<*>
)
The heavy lifting is actually done by the ap-normalize library.
Synopsis
- gfoldMap :: (Generic1 f, GFoldable (Rep1 f), Monoid m) => (a -> m) -> f a -> m
- gtraverse :: (Generic1 f, GTraversable (Rep1 f), Applicative m) => (a -> m b) -> f a -> m (f b)
- gsequenceA :: (Generic1 f, GTraversable (Rep1 f), Applicative m) => f (m a) -> m (f a)
- class GFoldable_ t => GFoldable t
- class GTraversable_ t => GTraversable t
- class (GFoldMap t, Foldable t) => GFoldable_ t
- class (GTraverse Kleisli t, GTraverse Equal t) => GTraversable_ t
- data Maybe' m
- type EndoM m = Endo (Maybe' m)
- liftEndoM :: Monoid m => m -> EndoM m
- lowerEndoM :: Monoid m => EndoM m -> m
- lowerMaybe :: Monoid m => Maybe' m -> m
- class GFoldMap t where
- data Equal (f :: Type -> Type) a b where
- newtype Kleisli f a b = Kleisli (a -> f b)
- class GTraverse arr t where
- gtraverse_ :: Applicative f => arr f a b -> t a -> Aps f (t b)
Library
gtraverse :: (Generic1 f, GTraversable (Rep1 f), Applicative m) => (a -> m b) -> f a -> m (f b) Source #
Generic traverse
.
instanceTraversable
MyTypeF wheretraverse
=gtraverse
gsequenceA :: (Generic1 f, GTraversable (Rep1 f), Applicative m) => f (m a) -> m (f a) Source #
class GFoldable_ t => GFoldable t Source #
Class of generic representations for which Foldable
can be derived.
Instances
GFoldable_ t => GFoldable t Source # | |
Defined in Generic.Data.Internal.Traversable |
class GTraversable_ t => GTraversable t Source #
Class of generic representations for which Traversable
can be derived.
Instances
GTraversable_ t => GTraversable t Source # | |
Defined in Generic.Data.Internal.Traversable |
class (GFoldMap t, Foldable t) => GFoldable_ t Source #
Internal definition of GFoldable
.
Instances
(GFoldMap t, Foldable t) => GFoldable_ t Source # | |
Defined in Generic.Data.Internal.Traversable |
class (GTraverse Kleisli t, GTraverse Equal t) => GTraversable_ t Source #
Internal definition of GTraversable
.
Instances
(GTraverse Kleisli t, GTraverse Equal t) => GTraversable_ t Source # | |
Defined in Generic.Data.Internal.Traversable |
Foldable
Isomorphic to Maybe m
, but we need to micromanage the
use of Monoid vs Semigroup to match exactly the output
of stock deriving, for inspection testing.
lowerEndoM :: Monoid m => EndoM m -> m Source #
lowerMaybe :: Monoid m => Maybe' m -> m Source #
class GFoldMap t where Source #
Instances
GFoldMap Par1 Source # | |
GFoldMap (V1 :: Type -> Type) Source # | |
GFoldMap (U1 :: Type -> Type) Source # | |
Foldable t => GFoldMap (Rec1 t) Source # | |
GFoldMap (K1 i a :: Type -> Type) Source # | |
(GFoldMap f, GFoldMap g) => GFoldMap (f :+: g) Source # | |
(GFoldMap f, GFoldMap g) => GFoldMap (f :*: g) Source # | |
GFoldMap f => GFoldMap (M1 i c f) Source # | |
(Foldable t, Foldable f) => GFoldMap (t :.: f) Source # | |
Traversable
data Equal (f :: Type -> Type) a b where Source #
Instances
GTraverse Equal Par1 Source # | |
Defined in Generic.Data.Internal.Traversable gtraverse_ :: forall (f :: Type -> Type) a b. Applicative f => Equal f a b -> Par1 a -> Aps f (Par1 b) Source # | |
Traversable t => GTraverse Equal (Rec1 t) Source # | |
Defined in Generic.Data.Internal.Traversable gtraverse_ :: forall (f :: Type -> Type) a b. Applicative f => Equal f a b -> Rec1 t a -> Aps f (Rec1 t b) Source # | |
(Traversable t, Traversable f) => GTraverse Equal (t :.: f) Source # | |
Defined in Generic.Data.Internal.Traversable gtraverse_ :: forall (f0 :: Type -> Type) a b. Applicative f0 => Equal f0 a b -> (t :.: f) a -> Aps f0 ((t :.: f) b) Source # |
newtype Kleisli f a b Source #
Kleisli (a -> f b) |
Instances
GTraverse Kleisli Par1 Source # | |
Defined in Generic.Data.Internal.Traversable gtraverse_ :: forall (f :: Type -> Type) a b. Applicative f => Kleisli f a b -> Par1 a -> Aps f (Par1 b) Source # | |
Traversable t => GTraverse Kleisli (Rec1 t) Source # | |
Defined in Generic.Data.Internal.Traversable gtraverse_ :: forall (f :: Type -> Type) a b. Applicative f => Kleisli f a b -> Rec1 t a -> Aps f (Rec1 t b) Source # | |
(Traversable t, Traversable f) => GTraverse Kleisli (t :.: f) Source # | |
Defined in Generic.Data.Internal.Traversable gtraverse_ :: forall (f0 :: Type -> Type) a b. Applicative f0 => Kleisli f0 a b -> (t :.: f) a -> Aps f0 ((t :.: f) b) Source # |
class GTraverse arr t where Source #
gtraverse_ :: Applicative f => arr f a b -> t a -> Aps f (t b) Source #