Copyright | (c) Justin Le 2019 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module provides tools for working with binary functor combinators that represent interpretable schemas.
These are types
that take two functors HBifunctor
tf
and g
and returns a new
functor t f g
, that "mixes together" f
and g
in some way.
The high-level usage of this is
biretract
::SemigroupIn
t f => t f f ~> f
which lets you fully "mix" together the two input functors.
biretract
:: (f:+:
f) a -> f a biretract ::Plus
f => (f:*:
f) a -> f a biretract ::Applicative
f =>Day
f f a -> f a biretract ::Monad
f =>Comp
f f a -> f a
See Data.HBifunctor.Tensor for the next stage of structure in tensors and moving in and out of them.
Synopsis
- class (HBifunctor t, Inject (NonEmptyBy t)) => Associative t where
- type NonEmptyBy t :: (Type -> Type) -> Type -> Type
- type FunctorBy t :: (Type -> Type) -> Constraint
- associating :: (FunctorBy t f, FunctorBy t g, FunctorBy t h) => t f (t g h) <~> t (t f g) h
- appendNE :: t (NonEmptyBy t f) (NonEmptyBy t f) ~> NonEmptyBy t f
- matchNE :: FunctorBy t f => NonEmptyBy t f ~> (f :+: t f (NonEmptyBy t f))
- consNE :: t f (NonEmptyBy t f) ~> NonEmptyBy t f
- toNonEmptyBy :: t f f ~> NonEmptyBy t f
- assoc :: (Associative t, FunctorBy t f, FunctorBy t g, FunctorBy t h) => t f (t g h) ~> t (t f g) h
- disassoc :: (Associative t, FunctorBy t f, FunctorBy t g, FunctorBy t h) => t (t f g) h ~> t f (t g h)
- class (Associative t, FunctorBy t f) => SemigroupIn t f where
- matchingNE :: (Associative t, FunctorBy t f) => NonEmptyBy t f <~> (f :+: t f (NonEmptyBy t f))
- retractNE :: forall t f. SemigroupIn t f => NonEmptyBy t f ~> f
- interpretNE :: forall t g f. SemigroupIn t f => (g ~> f) -> NonEmptyBy t g ~> f
- biget :: SemigroupIn t (AltConst b) => (forall x. f x -> b) -> (forall x. g x -> b) -> t f g a -> b
- biapply :: SemigroupIn t (Op b) => (forall x. f x -> x -> b) -> (forall x. g x -> x -> b) -> t f g a -> a -> b
- (!*!) :: SemigroupIn t h => (f ~> h) -> (g ~> h) -> t f g ~> h
- (!$!) :: SemigroupIn t (AltConst b) => (forall x. f x -> b) -> (forall x. g x -> b) -> t f g a -> b
- (!+!) :: (f ~> h) -> (g ~> h) -> (f :+: g) ~> h
- newtype WrapHBF t f g a = WrapHBF {
- unwrapHBF :: t f g a
- newtype WrapNE t f a = WrapNE {
- unwrapNE :: NonEmptyBy t f a
Associative
class (HBifunctor t, Inject (NonEmptyBy t)) => Associative t where Source #
An HBifunctor
where it doesn't matter which binds first is
Associative
. Knowing this gives us a lot of power to rearrange the
internals of our HFunctor
at will.
For example, for the functor product:
data (f :*:
g) a = f a :*: g a
We know that f :*: (g :*: h)
is the same as (f :*: g) :*: h
.
Formally, we can say that t
enriches a the category of
endofunctors with semigroup strcture: it turns our endofunctor category
into a "semigroupoidal category".
Different instances of t
each enrich the endofunctor category in
different ways, giving a different semigroupoidal category.
type NonEmptyBy t :: (Type -> Type) -> Type -> Type Source #
The "semigroup functor combinator" generated by t
.
A value of type NonEmptyBy t f a
is equivalent to one of:
f a
t f f a
t f (t f f) a
t f (t f (t f f)) a
t f (t f (t f (t f f))) a
- .. etc
For example, for :*:
, we have NonEmptyF
. This is because:
x ~NonEmptyF
(x:|
[]) ~inject
x x:*:
y ~ NonEmptyF (x :| [y]) ~toNonEmptyBy
(x :*: y) x :*: y :*: z ~ NonEmptyF (x :| [y,z]) -- etc.
You can create an "singleton" one with inject
, or else one from
a single t f f
with toNonEmptyBy
.
See ListBy
for a "possibly empty" version
of this type.
type FunctorBy t :: (Type -> Type) -> Constraint Source #
A description of "what type of Functor" this tensor is expected to
be applied to. This should typically always be either Functor
,
Contravariant
, or Invariant
.
Since: 0.3.0.0
type FunctorBy t = Unconstrained
associating :: (FunctorBy t f, FunctorBy t g, FunctorBy t h) => t f (t g h) <~> t (t f g) h Source #
The isomorphism between t f (t g h) a
and t (t f g) h a
. To
use this isomorphism, see assoc
and disassoc
.
appendNE :: t (NonEmptyBy t f) (NonEmptyBy t f) ~> NonEmptyBy t f Source #
If a
represents multiple applications of NonEmptyBy
t ft f
to
itself, then we can also "append" two
s applied to
themselves into one giant NonEmptyBy
t f
containing all of the NonEmptyBy
t ft f
s.
Note that this essentially gives an instance for
, for any functor SemigroupIn
t (NonEmptyBy t f)f
.
matchNE :: FunctorBy t f => NonEmptyBy t f ~> (f :+: t f (NonEmptyBy t f)) Source #
If a
represents multiple applications of NonEmptyBy
t ft f
to itself, then we can split it based on whether or not it is just
a single f
or at least one top-level application of t f
.
Note that you can recursively "unroll" a NonEmptyBy
completely
into a Chain1
by using
unrollNE
.
consNE :: t f (NonEmptyBy t f) ~> NonEmptyBy t f Source #
Prepend an application of t f
to the front of a
.NonEmptyBy
t f
toNonEmptyBy :: t f f ~> NonEmptyBy t f Source #
Embed a direct application of f
to itself into a
.NonEmptyBy
t f
Instances
assoc :: (Associative t, FunctorBy t f, FunctorBy t g, FunctorBy t h) => t f (t g h) ~> t (t f g) h Source #
Reassociate an application of t
.
disassoc :: (Associative t, FunctorBy t f, FunctorBy t g, FunctorBy t h) => t (t f g) h ~> t f (t g h) Source #
Reassociate an application of t
.
SemigroupIn
class (Associative t, FunctorBy t f) => SemigroupIn t f where Source #
For different
, we have functors Associative
tf
that we can
"squash", using biretract
:
t f f ~> f
This gives us the ability to squash applications of t
.
Formally, if we have
, we are enriching the category of
endofunctors with semigroup structure, turning it into a semigroupoidal
category. Different choices of Associative
tt
give different semigroupoidal
categories.
A functor f
is known as a "semigroup in the (semigroupoidal) category
of endofunctors on t
" if we can biretract
:
t f f ~> f
This gives us a few interesting results in category theory, which you can stil reading about if you don't care:
- All functors are semigroups in the semigroupoidal category
on
:+:
- The class of functors that are semigroups in the semigroupoidal
category on
:*:
is exactly the functors that are instances ofAlt
. - The class of functors that are semigroups in the semigroupoidal
category on
Day
is exactly the functors that are instances ofApply
. - The class of functors that are semigroups in the semigroupoidal
category on
Comp
is exactly the functors that are instances ofBind
.
Note that instances of this class are intended to be written with t
as a fixed type constructor, and f
to be allowed to vary freely:
instance Bind f => SemigroupIn Comp f
Any other sort of instance and it's easy to run into problems with type
inference. If you want to write an instance that's "polymorphic" on
tensor choice, use the WrapHBF
newtype wrapper over a type variable,
where the second argument also uses a type constructor:
instance SemigroupIn (WrapHBF t) (MyFunctor t i)
This will prevent problems with overloaded instances.
Nothing
biretract :: t f f ~> f Source #
The HBifunctor
analogy of retract
. It retracts both f
s
into a single f
, effectively fully mixing them together.
This function makes f
a semigroup in the category of endofunctors
with respect to tensor t
.
binterpret :: (g ~> f) -> (h ~> f) -> t g h ~> f Source #
The HBifunctor
analogy of interpret
. It takes two
interpreting functions, and mixes them together into a target
functor h
.
Note that this is useful in the poly-kinded case, but it is not possible
to define generically for all SemigroupIn
because it only is defined
for Type -> Type
inputes. See !+!
for a version that is poly-kinded
for :+:
in specific.
default binterpret :: Interpret (NonEmptyBy t) f => (g ~> f) -> (h ~> f) -> t g h ~> f Source #
Instances
Decide f => SemigroupIn Night f Source # | Since: 0.3.0.0 |
Inalt f => SemigroupIn Night f Source # | Since: 0.4.0.0 |
Divise f => SemigroupIn Day f Source # | Since: 0.3.0.0 |
Apply f => SemigroupIn Day f Source # | Instances of |
Inply f => SemigroupIn Day f Source # | Since: 0.4.0.0 |
Alt f => SemigroupIn These1 f Source # | |
Alt f => SemigroupIn (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # | Instances of |
SemigroupIn (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # | All functors are semigroups in the semigroupoidal category on |
Alt f => SemigroupIn ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # | Instances of |
SemigroupIn ((:+:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # | All functors are semigroups in the semigroupoidal category on |
Bind f => SemigroupIn (Comp :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # | Instances of |
SemigroupIn (Joker :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # | |
SemigroupIn (LeftF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # | |
SemigroupIn (RightF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # | |
SemigroupIn (Void3 :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # | All functors are semigroups in the semigroupoidal category on |
(Associative t, FunctorBy t f, FunctorBy t (WrapNE t f)) => SemigroupIn (WrapHBF t) (WrapNE t f) Source # | |
(Tensor t i, FunctorBy t f, FunctorBy t (WrapLB t f)) => SemigroupIn (WrapHBF t) (WrapLB t f) Source # | |
(Associative t, FunctorBy t f, FunctorBy t (Chain1 t f)) => SemigroupIn (WrapHBF t) (Chain1 t f) Source # |
|
(Tensor t i, FunctorBy t (Chain t i f)) => SemigroupIn (WrapHBF t) (Chain t i f) Source # | We have to wrap |
matchingNE :: (Associative t, FunctorBy t f) => NonEmptyBy t f <~> (f :+: t f (NonEmptyBy t f)) Source #
An
represents the successive application of NonEmptyBy
t ft
to f
,
over and over again. So, that means that an
must either be
a single NonEmptyBy
t ff
, or an t f (NonEmptyBy t f)
.
matchingNE
states that these two are isomorphic. Use matchNE
and
to convert between one and the other.inject
!*!
consNE
retractNE :: forall t f. SemigroupIn t f => NonEmptyBy t f ~> f Source #
An implementation of retract
that works for any instance of
for SemigroupIn
t
.NonEmptyBy
t
Can be useful as a default implementation if you already have
SemigroupIn
implemented.
interpretNE :: forall t g f. SemigroupIn t f => (g ~> f) -> NonEmptyBy t g ~> f Source #
An implementation of interpret
that works for any instance of
for SemigroupIn
t
.NonEmptyBy
t
Can be useful as a default implementation if you already have
SemigroupIn
implemented.
Utility
biget :: SemigroupIn t (AltConst b) => (forall x. f x -> b) -> (forall x. g x -> b) -> t f g a -> b Source #
Useful wrapper over binterpret
to allow you to directly extract
a value b
out of the t f g a
, if you can convert an f x
and g x
into b
.
Note that depending on the constraints on h
in
,
you may have extra constraints on SemigroupIn
t hb
.
- If
h
is unconstrained, there are no constraints onb
- If
h
must beApply
,Alt
,Divise
, orDecide
,b
needs to be an instance ofSemigroup
- If
h
isApplicative
,Plus
,Divisible
, orConclude
,b
needs to be an instance ofMonoid
For some constraints (like Monad
), this will not be usable.
-- Return the length of either the list, or the Map, depending on which -- one s in the+
biget
length
length :: ([] :+:Map
Int
)Char
-> Int -- Return the length of both the list and the map, added togetherbiget
(Sum
. length) (Sum . length) ::Day
[] (Map Int) Char -> Sum Int
biapply :: SemigroupIn t (Op b) => (forall x. f x -> x -> b) -> (forall x. g x -> x -> b) -> t f g a -> a -> b Source #
Useful wrapper over binterpret
to allow you to directly extract
a value b
out of the t f g a
, if you can convert an f x
and g x
into b
, given an x
input.
Note that depending on the constraints on h
in
,
you may have extra constraints on SemigroupIn
t hb
.
- If
h
is unconstrained, there are no constraints onb
- If
h
must beDivise
, orDivisible
,b
needs to be an instance ofSemigroup
- If
h
must beDivisible
, thenb
needs to be an instance ofMonoid
.
For some constraints (like Monad
), this will not be usable.
Since: 0.3.2.0
(!*!) :: SemigroupIn t h => (f ~> h) -> (g ~> h) -> t f g ~> h infixr 5 Source #
Infix alias for binterpret
Note that this is useful in the poly-kinded case, but it is not possible
to define generically for all SemigroupIn
because it only is defined
for Type -> Type
inputes. See !+!
for a version that is poly-kinded
for :+:
in specific.
(!$!) :: SemigroupIn t (AltConst b) => (forall x. f x -> b) -> (forall x. g x -> b) -> t f g a -> b infixr 5 Source #
newtype WrapHBF t f g a Source #
A newtype wrapper meant to be used to define polymorphic SemigroupIn
instances. See documentation for SemigroupIn
for more information.
Please do not ever define an instance of SemigroupIn
"naked" on the
second parameter:
instance SemigroupIn (WrapHBF t) f
As that would globally ruin everything using WrapHBF
.
Instances
HBifunctor t => HFunctor (WrapHBF t f :: (k -> Type) -> k -> Type) Source # | |
HBifunctor t => HBifunctor (WrapHBF t :: (k -> Type) -> (k -> Type) -> k -> Type) Source # | |
Defined in Data.HBifunctor.Associative hleft :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type). (f ~> j) -> WrapHBF t f g ~> WrapHBF t j g Source # hright :: forall (g :: k0 -> Type) (l :: k0 -> Type) (f :: k0 -> Type). (g ~> l) -> WrapHBF t f g ~> WrapHBF t f l Source # hbimap :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type) (l :: k0 -> Type). (f ~> j) -> (g ~> l) -> WrapHBF t f g ~> WrapHBF t j l Source # | |
Associative t => Associative (WrapHBF t) Source # | |
Defined in Data.HBifunctor.Associative type NonEmptyBy (WrapHBF t) :: (Type -> Type) -> Type -> Type Source # type FunctorBy (WrapHBF t) :: (Type -> Type) -> Constraint Source # associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy (WrapHBF t) f, FunctorBy (WrapHBF t) g, FunctorBy (WrapHBF t) h) => WrapHBF t f (WrapHBF t g h) <~> WrapHBF t (WrapHBF t f g) h Source # appendNE :: forall (f :: Type -> Type). WrapHBF t (NonEmptyBy (WrapHBF t) f) (NonEmptyBy (WrapHBF t) f) ~> NonEmptyBy (WrapHBF t) f Source # matchNE :: forall (f :: Type -> Type). FunctorBy (WrapHBF t) f => NonEmptyBy (WrapHBF t) f ~> (f :+: WrapHBF t f (NonEmptyBy (WrapHBF t) f)) Source # consNE :: forall (f :: Type -> Type). WrapHBF t f (NonEmptyBy (WrapHBF t) f) ~> NonEmptyBy (WrapHBF t) f Source # toNonEmptyBy :: forall (f :: Type -> Type). WrapHBF t f f ~> NonEmptyBy (WrapHBF t) f Source # | |
(Associative t, FunctorBy t f, FunctorBy t (WrapNE t f)) => SemigroupIn (WrapHBF t) (WrapNE t f) Source # | |
(Tensor t i, FunctorBy t f, FunctorBy t (WrapLB t f)) => SemigroupIn (WrapHBF t) (WrapLB t f) Source # | |
Tensor t i => Tensor (WrapHBF t) (WrapF i) Source # | |
Defined in Data.HBifunctor.Tensor intro1 :: forall (f :: Type -> Type). f ~> WrapHBF t f (WrapF i) Source # intro2 :: forall (g :: Type -> Type). g ~> WrapHBF t (WrapF i) g Source # elim1 :: forall (f :: Type -> Type). FunctorBy (WrapHBF t) f => WrapHBF t f (WrapF i) ~> f Source # elim2 :: forall (g :: Type -> Type). FunctorBy (WrapHBF t) g => WrapHBF t (WrapF i) g ~> g Source # appendLB :: forall (f :: Type -> Type). WrapHBF t (ListBy (WrapHBF t) f) (ListBy (WrapHBF t) f) ~> ListBy (WrapHBF t) f Source # splitNE :: forall (f :: Type -> Type). NonEmptyBy (WrapHBF t) f ~> WrapHBF t f (ListBy (WrapHBF t) f) Source # splittingLB :: forall (f :: Type -> Type). ListBy (WrapHBF t) f <~> (WrapF i :+: WrapHBF t f (ListBy (WrapHBF t) f)) Source # toListBy :: forall (f :: Type -> Type). WrapHBF t f f ~> ListBy (WrapHBF t) f Source # fromNE :: forall (f :: Type -> Type). NonEmptyBy (WrapHBF t) f ~> ListBy (WrapHBF t) f Source # | |
(Tensor t i, FunctorBy t f, FunctorBy t (WrapLB t f)) => MonoidIn (WrapHBF t) (WrapF i) (WrapLB t f) Source # | |
(Tensor t i, FunctorBy t (Chain t i f)) => MonoidIn (WrapHBF t) (WrapF i) (Chain t i f) Source # |
|
(Associative t, FunctorBy t f, FunctorBy t (Chain1 t f)) => SemigroupIn (WrapHBF t) (Chain1 t f) Source # |
|
(Tensor t i, FunctorBy t (Chain t i f)) => SemigroupIn (WrapHBF t) (Chain t i f) Source # | We have to wrap |
Foldable (t f g) => Foldable (WrapHBF t f g) Source # | |
Defined in Data.HBifunctor.Associative fold :: Monoid m => WrapHBF t f g m -> m # foldMap :: Monoid m => (a -> m) -> WrapHBF t f g a -> m # foldMap' :: Monoid m => (a -> m) -> WrapHBF t f g a -> m # foldr :: (a -> b -> b) -> b -> WrapHBF t f g a -> b # foldr' :: (a -> b -> b) -> b -> WrapHBF t f g a -> b # foldl :: (b -> a -> b) -> b -> WrapHBF t f g a -> b # foldl' :: (b -> a -> b) -> b -> WrapHBF t f g a -> b # foldr1 :: (a -> a -> a) -> WrapHBF t f g a -> a # foldl1 :: (a -> a -> a) -> WrapHBF t f g a -> a # toList :: WrapHBF t f g a -> [a] # null :: WrapHBF t f g a -> Bool # length :: WrapHBF t f g a -> Int # elem :: Eq a => a -> WrapHBF t f g a -> Bool # maximum :: Ord a => WrapHBF t f g a -> a # minimum :: Ord a => WrapHBF t f g a -> a # | |
Eq1 (t f g) => Eq1 (WrapHBF t f g) Source # | |
Ord1 (t f g) => Ord1 (WrapHBF t f g) Source # | |
Defined in Data.HBifunctor.Associative | |
Show1 (t f g) => Show1 (WrapHBF t f g) Source # | |
Traversable (t f g) => Traversable (WrapHBF t f g) Source # | |
Defined in Data.HBifunctor.Associative traverse :: Applicative f0 => (a -> f0 b) -> WrapHBF t f g a -> f0 (WrapHBF t f g b) # sequenceA :: Applicative f0 => WrapHBF t f g (f0 a) -> f0 (WrapHBF t f g a) # mapM :: Monad m => (a -> m b) -> WrapHBF t f g a -> m (WrapHBF t f g b) # sequence :: Monad m => WrapHBF t f g (m a) -> m (WrapHBF t f g a) # | |
Functor (t f g) => Functor (WrapHBF t f g) Source # | |
(Typeable f, Typeable g, Typeable a, Typeable t, Typeable k1, Typeable k2, Typeable k3, Data (t f g a)) => Data (WrapHBF t f g a) Source # | |
Defined in Data.HBifunctor.Associative gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> WrapHBF t f g a -> c (WrapHBF t f g a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WrapHBF t f g a) # toConstr :: WrapHBF t f g a -> Constr # dataTypeOf :: WrapHBF t f g a -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (WrapHBF t f g a)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (WrapHBF t f g a)) # gmapT :: (forall b. Data b => b -> b) -> WrapHBF t f g a -> WrapHBF t f g a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WrapHBF t f g a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WrapHBF t f g a -> r # gmapQ :: (forall d. Data d => d -> u) -> WrapHBF t f g a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WrapHBF t f g a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WrapHBF t f g a -> m (WrapHBF t f g a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WrapHBF t f g a -> m (WrapHBF t f g a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WrapHBF t f g a -> m (WrapHBF t f g a) # | |
Generic (WrapHBF t f g a) Source # | |
Read (t f g a) => Read (WrapHBF t f g a) Source # | |
Show (t f g a) => Show (WrapHBF t f g a) Source # | |
Eq (t f g a) => Eq (WrapHBF t f g a) Source # | |
Ord (t f g a) => Ord (WrapHBF t f g a) Source # | |
Defined in Data.HBifunctor.Associative compare :: WrapHBF t f g a -> WrapHBF t f g a -> Ordering # (<) :: WrapHBF t f g a -> WrapHBF t f g a -> Bool # (<=) :: WrapHBF t f g a -> WrapHBF t f g a -> Bool # (>) :: WrapHBF t f g a -> WrapHBF t f g a -> Bool # (>=) :: WrapHBF t f g a -> WrapHBF t f g a -> Bool # max :: WrapHBF t f g a -> WrapHBF t f g a -> WrapHBF t f g a # min :: WrapHBF t f g a -> WrapHBF t f g a -> WrapHBF t f g a # | |
type FunctorBy (WrapHBF t) Source # | |
Defined in Data.HBifunctor.Associative | |
type NonEmptyBy (WrapHBF t) Source # | |
Defined in Data.HBifunctor.Associative | |
type ListBy (WrapHBF t) Source # | |
Defined in Data.HBifunctor.Tensor | |
type Rep (WrapHBF t f g a) Source # | |
Defined in Data.HBifunctor.Associative |
Any
is a NonEmptyBy
t f
if we have
SemigroupIn
t
. This newtype wrapper witnesses that fact. We require
a newtype wrapper to avoid overlapping instances.Associative
t
WrapNE | |
|
Instances
Contravariant (NonEmptyBy t f) => Contravariant (WrapNE t f) Source # | |
Functor (NonEmptyBy t f) => Functor (WrapNE t f) Source # | |
Invariant (NonEmptyBy t f) => Invariant (WrapNE t f) Source # | |
Defined in Data.HBifunctor.Associative | |
(Associative t, FunctorBy t f, FunctorBy t (WrapNE t f)) => SemigroupIn (WrapHBF t) (WrapNE t f) Source # | |