semigroupoids-6: Semigroupoids: Category sans id
Copyright(C) 2021 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Functor.Contravariant.Decide

Description

 
Synopsis

Documentation

class Contravariant f => Decide f where Source #

The contravariant analogue of Alt.

If one thinks of f a as a consumer of as, then decide allows one to handle the consumption of a value by choosing to handle it via exactly one of two independent consumers. It redirects the input completely into one of two consumers.

decide takes the "decision" method and the two potential consumers, and returns the wrapped/combined consumer.

Mathematically, a functor being an instance of Decide means that it is "semigroupoidal" with respect to the contravariant "either-based" Day convolution (data EitherDay f g a = forall b c. EitherDay (f b) (g c) (a -> Either b c)). That is, it is possible to define a function (f EitherDay f) a -> f a in a way that is associative.

Since: 5.3.6

Methods

decide :: (a -> Either b c) -> f b -> f c -> f a Source #

Takes the "decision" method and the two potential consumers, and returns the wrapped/combined consumer.

Instances

Instances details
Decide Comparison Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> Comparison b -> Comparison c -> Comparison a Source #

Decide Equivalence Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> Equivalence b -> Equivalence c -> Equivalence a Source #

Decide Predicate Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> Predicate b -> Predicate c -> Predicate a Source #

Decide (Op r) Source #

Unlike Decidable, requires no constraint on r.

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> Op r b -> Op r c -> Op r a Source #

Decide (Proxy :: Type -> Type) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> Proxy b -> Proxy c -> Proxy a Source #

Decide (U1 :: Type -> Type) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> U1 b -> U1 c -> U1 a Source #

Decide (V1 :: Type -> Type) Source #

Has no Decidable or Conclude instance.

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> V1 b -> V1 c -> V1 a Source #

Decidable f => Decide (WrappedDivisible f) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> WrappedDivisible f b -> WrappedDivisible f c -> WrappedDivisible f a Source #

Divise m => Decide (ListT m) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> ListT m b -> ListT m c -> ListT m a Source #

Divise m => Decide (MaybeT m) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> MaybeT m b -> MaybeT m c -> MaybeT m a Source #

Decide f => Decide (Alt f) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> Alt f b -> Alt f c -> Alt f a Source #

Decide f => Decide (Rec1 f) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> Rec1 f b -> Rec1 f c -> Rec1 f a Source #

Decide f => Decide (Backwards f) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> Backwards f b -> Backwards f c -> Backwards f a Source #

Decide f => Decide (IdentityT f) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> IdentityT f b -> IdentityT f c -> IdentityT f a Source #

Decide m => Decide (ReaderT r m) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> ReaderT r m b -> ReaderT r m c -> ReaderT r m a Source #

Decide m => Decide (StateT s m) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> StateT s m b -> StateT s m c -> StateT s m a Source #

Decide m => Decide (StateT s m) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> StateT s m b -> StateT s m c -> StateT s m a Source #

Decide m => Decide (WriterT w m) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> WriterT w m b -> WriterT w m c -> WriterT w m a Source #

Decide m => Decide (WriterT w m) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> WriterT w m b -> WriterT w m c -> WriterT w m a Source #

Decide f => Decide (Reverse f) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> Reverse f b -> Reverse f c -> Reverse f a Source #

(Decide f, Decide g) => Decide (Product f g) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> Product f g b -> Product f g c -> Product f g a Source #

(Decide f, Decide g) => Decide (f :*: g) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> (f :*: g) b -> (f :*: g) c -> (f :*: g) a Source #

(Apply f, Decide g) => Decide (Compose f g) Source #

Unlike Decidable, requires only Apply on f.

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> Compose f g b -> Compose f g c -> Compose f g a Source #

(Apply f, Decide g) => Decide (f :.: g) Source #

Unlike Decidable, requires only Apply on f.

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> (f :.: g) b -> (f :.: g) c -> (f :.: g) a Source #

Decide f => Decide (M1 i c f) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c0) -> M1 i c f b -> M1 i c f c0 -> M1 i c f a Source #

Decide m => Decide (RWST r w s m) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> RWST r w s m b -> RWST r w s m c -> RWST r w s m a Source #

Decide m => Decide (RWST r w s m) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

decide :: (a -> Either b c) -> RWST r w s m b -> RWST r w s m c -> RWST r w s m a Source #

gdecide :: (Generic1 f, Decide (Rep1 f)) => (a -> Either b c) -> f b -> f c -> f a Source #

Generic decide. Caveats:

  1. Will not compile if f is a sum type.
  2. Will not compile if f contains fields that do not mention its type variable.
  3. -XDeriveGeneric is not smart enough to make instances where the type variable appears in negative position.

Since: 5.3.8

decided :: Decide f => f b -> f c -> f (Either b c) Source #

For decided x y, the resulting f (Either b c) will direct Lefts to be consumed by x, and Rights to be consumed by y.

Since: 5.3.6

gdecided :: (Generic1 f, Decide (Rep1 f)) => f b -> f c -> f (Either b c) Source #

Generic decided. Caveats are the same as for gdecide.

Since: 5.3.8