Copyright | (C) 2021 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Synopsis
- class Contravariant f => Divise f where
- divise :: (a -> (b, c)) -> f b -> f c -> f a
- divised :: Divise f => f a -> f b -> f (a, b)
- newtype WrappedDivisible f a = WrapDivisible {
- unwrapDivisible :: f a
Documentation
class Contravariant f => Divise f where Source #
The contravariant analogue of Apply
; it is
Divisible
without conquer
.
If one thinks of f a
as a consumer of a
s, then divise
allows one
to handle the consumption of a value by splitting it between two
consumers that consume separate parts of a
.
divise
takes the "splitting" method and the two sub-consumers, and
returns the wrapped/combined consumer.
All instances of Divisible
should be instances of Divise
with
.divise
= divide
If a function is polymorphic over
(as opposed to Divise
f
), we can provide a stronger guarantee: namely, that any input consumed
will be passed to at least one sub-consumer. With Divisible
f
, said input
could potentially disappear into the void, as this is possible with
Divisible
fconquer
.
Mathematically, a functor being an instance of Divise
means that it is
"semigroupoidal" with respect to the contravariant (tupling) Day
convolution. That is, it is possible to define a function (f
in a way that is associative.Day
f)
a -> f a
Since: 5.3.6
divise :: (a -> (b, c)) -> f b -> f c -> f a Source #
Takes a "splitting" method and the two sub-consumers, and returns the wrapped/combined consumer.
Instances
Divise Predicate Source # | Since: 5.3.6 |
Divise Comparison Source # | Since: 5.3.6 |
Defined in Data.Functor.Contravariant.Divise divise :: (a -> (b, c)) -> Comparison b -> Comparison c -> Comparison a Source # | |
Divise Equivalence Source # | Since: 5.3.6 |
Defined in Data.Functor.Contravariant.Divise divise :: (a -> (b, c)) -> Equivalence b -> Equivalence c -> Equivalence a Source # | |
Divise (V1 :: Type -> Type) Source # | Has no Since: 5.3.6 |
Divise (U1 :: Type -> Type) Source # | Since: 5.3.6 |
Semigroup r => Divise (Op r) Source # | Unlike Since: 5.3.6 |
Divise (Proxy :: Type -> Type) Source # | Since: 5.3.6 |
Divise m => Divise (MaybeT m) Source # | Since: 5.3.6 |
Divise m => Divise (ListT m) Source # | Since: 5.3.6 |
Divisible f => Divise (WrappedDivisible f) Source # | Since: 5.3.6 |
Defined in Data.Functor.Contravariant.Divise divise :: (a -> (b, c)) -> WrappedDivisible f b -> WrappedDivisible f c -> WrappedDivisible f a Source # | |
Divise f => Divise (Rec1 f) Source # | Since: 5.3.6 |
Semigroup m => Divise (Const m :: Type -> Type) Source # | Unlike Since: 5.3.6 |
Divise f => Divise (Alt f) Source # | Since: 5.3.6 |
Divise f => Divise (IdentityT f) Source # | Since: 5.3.6 |
Divise f => Divise (Reverse f) Source # | Since: 5.3.6 |
Semigroup m => Divise (Constant m :: Type -> Type) Source # | Unlike Since: 5.3.6 |
Divise m => Divise (WriterT w m) Source # | Since: 5.3.6 |
Divise m => Divise (WriterT w m) Source # | Since: 5.3.6 |
Divise m => Divise (StateT s m) Source # | Since: 5.3.6 |
Divise m => Divise (StateT s m) Source # | Since: 5.3.6 |
Divise m => Divise (ReaderT r m) Source # | Since: 5.3.6 |
Divise m => Divise (ExceptT e m) Source # | Since: 5.3.6 |
Divise m => Divise (ErrorT e m) Source # | Since: 5.3.6 |
Divise f => Divise (Backwards f) Source # | Since: 5.3.6 |
(Divise f, Divise g) => Divise (f :*: g) Source # | Since: 5.3.6 |
(Divise f, Divise g) => Divise (Product f g) Source # | Since: 5.3.6 |
Divise f => Divise (M1 i c f) Source # | Since: 5.3.6 |
(Apply f, Divise g) => Divise (f :.: g) Source # | Unlike Since: 5.3.6 |
(Apply f, Divise g) => Divise (Compose f g) Source # | Unlike Since: 5.3.6 |
Divise m => Divise (RWST r w s m) Source # | Since: 5.3.6 |
Divise m => Divise (RWST r w s m) Source # | Since: 5.3.6 |
newtype WrappedDivisible f a Source #
WrapDivisible | |
|
Instances
Contravariant f => Contravariant (WrappedDivisible f) Source # | Since: 5.3.6 |
Defined in Data.Functor.Contravariant.Divise contramap :: (a -> b) -> WrappedDivisible f b -> WrappedDivisible f a # (>$) :: b -> WrappedDivisible f b -> WrappedDivisible f a # | |
Divisible f => Divise (WrappedDivisible f) Source # | Since: 5.3.6 |
Defined in Data.Functor.Contravariant.Divise divise :: (a -> (b, c)) -> WrappedDivisible f b -> WrappedDivisible f c -> WrappedDivisible f a Source # | |
Decidable f => Decide (WrappedDivisible f) Source # | Since: 5.3.6 |
Defined in Data.Functor.Contravariant.Decide decide :: (a -> Either b c) -> WrappedDivisible f b -> WrappedDivisible f c -> WrappedDivisible f a Source # | |
Decidable f => Conclude (WrappedDivisible f) Source # | Since: 5.3.6 |
Defined in Data.Functor.Contravariant.Conclude conclude :: (a -> Void) -> WrappedDivisible f a Source # |