functor-combinators-0.3.4.0: Tools for functor combinator-based program design
Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Functor.Contravariant.Decide

Description

The contravariant counterpart of Alt: like Decidable, but without loss or a superclass constraint on Divisible. This is only a part of this library currently for compatibility, until it is (hopefully) merged into semigroupoids.

Since: 0.3.0.0

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 "semgroupoidal" 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.

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 Predicate Source # 
Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

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

Decide Comparison Source # 
Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

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

Decide Equivalence Source # 
Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

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

FreeOf Decide Dec1 Source #

Since: 0.3.0.0

Instance details

Defined in Data.HFunctor.Final

Associated Types

type FreeFunctorBy Dec1 :: (Type -> Type) -> Constraint Source #

Methods

fromFree :: forall (f :: Type -> Type). Dec1 f ~> Final Decide f Source #

toFree :: forall (f :: Type -> Type). FreeFunctorBy Dec1 f => Final Decide f ~> Dec1 f Source #

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

Defined in Data.Functor.Contravariant.Decide

Methods

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

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

Defined in Data.Functor.Contravariant.Decide

Methods

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

Decide (Op r) Source #

Unlike Decidable, requires no constraint on r

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 # 
Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

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

Divise m => Decide (MaybeT m) Source # 
Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

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

Divise m => Decide (ListT m) Source # 
Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

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

Decide (Dec1 f) Source # 
Instance details

Defined in Data.Functor.Contravariant.Divisible.Free

Methods

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

Decide (Dec f) Source # 
Instance details

Defined in Data.Functor.Contravariant.Divisible.Free

Methods

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

Decide f => Decide (Rec1 f) Source # 
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 (Alt f) Source # 
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 (IdentityT f) Source # 
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 # 
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 # 
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 # 
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 # 
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 # 
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 # 
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 (Backwards f) Source # 
Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

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

Decidable f => Decide (WrappedDivisible f) Source # 
Instance details

Defined in Data.Functor.Contravariant.Decide

Methods

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

Decide f => Decide (Step f) Source #

Since: 0.3.0.0

Instance details

Defined in Control.Applicative.Step

Methods

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

Decide f => Decide (ListF f) Source #

Since: 0.3.0.0

Instance details

Defined in Control.Applicative.ListF

Methods

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

Decide f => Decide (NonEmptyF f) Source #

Since: 0.3.0.0

Instance details

Defined in Control.Applicative.ListF

Methods

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

Decide f => Decide (MaybeF f) Source #

Since: 0.3.3.0

Instance details

Defined in Control.Applicative.ListF

Methods

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

Semigroup w => Decide (AltConst w :: Type -> Type) Source #

Unlike for Const, this is possible because there is no Decidable instance to complicate things.

Instance details

Defined in Data.HFunctor.Interpret

Methods

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

Contravariant (Final Decide f) Source #

Since: 0.3.0.0

Instance details

Defined in Data.HFunctor.Final

Methods

contramap :: (a -> b) -> Final Decide f b -> Final Decide f a #

(>$) :: b -> Final Decide f b -> Final Decide f a #

(Decide f, Decide g) => Decide (f :*: g) Source # 
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 g) => Decide (Product f g) Source # 
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 (ProxyF f :: Type -> Type) Source #

Since: 0.3.0.0

Instance details

Defined in Data.HFunctor

Methods

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

Contravariant f => Decide (Chain1 Night f) Source #

Chain1 Night is the free "semigroup in the semigroupoidal category of endofunctors enriched by Night" --- aka, the free Decide.

Since: 0.3.0.0

Instance details

Defined in Data.HFunctor.Chain

Methods

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

Decide (Final Decidable f) Source #

Since: 0.3.0.0

Instance details

Defined in Data.HFunctor.Final

Methods

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

Decide (Final Decide f) Source #

Since: 0.3.0.0

Instance details

Defined in Data.HFunctor.Final

Methods

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

Decide (Final Conclude f) Source #

Since: 0.3.0.0

Instance details

Defined in Data.HFunctor.Final

Methods

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

Decide f => Decide (M1 i c f) Source # 
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 #

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

Unlike Decidable, requires only Apply on f.

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.

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 #

Decide m => Decide (RWST r w s m) Source # 
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 # 
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 (Chain Night Not f) Source #

Since: 0.3.0.0

Instance details

Defined in Data.HFunctor.Chain

Methods

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

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.