proton-0.0.4
Safe HaskellNone
LanguageHaskell2010

Data.Profunctor.Coindexed

Documentation

class (Profunctor p, Profunctor q) => Coindexable e p q | q -> p where Source #

Minimal complete definition

Nothing

Methods

coindexed :: p a (Either e b) -> q a b Source #

default coindexed :: (e ~ Void, p ~ q) => p a (Either e b) -> q a b Source #

Instances

Instances details
Profunctor p => Coindexable i p (Coindexed i p) Source # 
Instance details

Defined in Data.Profunctor.Coindexed

Methods

coindexed :: p a (Either i b) -> Coindexed i p a b Source #

(Alternative f, Monad f) => Coindexable e (Star f) (Star f) Source # 
Instance details

Defined in Data.Profunctor.Coindexed

Methods

coindexed :: Star f a (Either e b) -> Star f a b Source #

Coindexable e (Forget r) (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Coindexed

Methods

coindexed :: Forget r a (Either e b) -> Forget r a b Source #

Functor f => Coindexable Void (Star f) (Star f) Source # 
Instance details

Defined in Data.Profunctor.Coindexed

Methods

coindexed :: Star f a (Either Void b) -> Star f a b Source #

Functor f => Coindexable Void (Costar f) (Costar f) Source # 
Instance details

Defined in Data.Profunctor.Coindexed

Methods

coindexed :: Costar f a (Either Void b) -> Costar f a b Source #

Coindexable Void (Tagged :: Type -> Type -> Type) (Tagged :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Coindexed

Methods

coindexed :: Tagged a (Either Void b) -> Tagged a b Source #

Coindexable Void ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Coindexed

Methods

coindexed :: (a -> Either Void b) -> a -> b Source #

data Coindexed e p a b Source #

Constructors

Coindexed 

Fields

Instances

Instances details
Profunctor p => Coindexable i p (Coindexed i p) Source # 
Instance details

Defined in Data.Profunctor.Coindexed

Methods

coindexed :: p a (Either i b) -> Coindexed i p a b Source #

Profunctor p => Profunctor (Coindexed e p) Source # 
Instance details

Defined in Data.Profunctor.Coindexed

Methods

dimap :: (a -> b) -> (c -> d) -> Coindexed e p b c -> Coindexed e p a d #

lmap :: (a -> b) -> Coindexed e p b c -> Coindexed e p a c #

rmap :: (b -> c) -> Coindexed e p a b -> Coindexed e p a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Coindexed e p a b -> Coindexed e p a c #

(.#) :: forall a b c q. Coercible b a => Coindexed e p b c -> q a b -> Coindexed e p a c #

Choice p => Choice (Coindexed i p) Source # 
Instance details

Defined in Data.Profunctor.Coindexed

Methods

left' :: Coindexed i p a b -> Coindexed i p (Either a c) (Either b c) #

right' :: Coindexed i p a b -> Coindexed i p (Either c a) (Either c b) #