proton-0.0.4
Safe HaskellNone
LanguageHaskell2010

Data.Profunctor.Indexed

Documentation

class (Profunctor p, Profunctor q) => Indexable i p q | p -> q where Source #

Minimal complete definition

Nothing

Methods

indexed :: p a b -> q (i, a) b Source #

default indexed :: p ~ q => p a b -> q (i, a) b Source #

Instances

Instances details
Indexable i (Tagged :: Type -> Type -> Type) (Tagged :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

indexed :: Tagged a b -> Tagged (i, a) b Source #

Functor f => Indexable i (Costar f) (Costar f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

indexed :: Costar f a b -> Costar f (i, a) b Source #

Functor f => Indexable i (Star f) (Star f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

indexed :: Star f a b -> Star f (i, a) b Source #

Indexable i (Forget r) (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

indexed :: Forget r a b -> Forget r (i, a) b Source #

Profunctor p => Indexable i (UnIndexed i p) p Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

indexed :: UnIndexed i p a b -> p (i, a) b Source #

Profunctor p => Indexable i (Indexed i p) p Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

indexed :: Indexed i p a b -> p (i, a) b Source #

Indexable i ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

indexed :: (a -> b) -> (i, a) -> b Source #

data Indexed i p a b Source #

Constructors

Indexed (p (i, a) b) 

Instances

Instances details
Profunctor p => Indexable i (Indexed i p) p Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

indexed :: Indexed i p a b -> p (i, a) b Source #

Profunctor p => Profunctor (Indexed i p) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> Indexed i p b c -> Indexed i p a d #

lmap :: (a -> b) -> Indexed i p b c -> Indexed i p a c #

rmap :: (b -> c) -> Indexed i p a b -> Indexed i p a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Indexed i p a b -> Indexed i p a c #

(.#) :: forall a b c q. Coercible b a => Indexed i p b c -> q a b -> Indexed i p a c #

Strong p => Strong (Indexed i p) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: Indexed i p a b -> Indexed i p (a, c) (b, c) #

second' :: Indexed i p a b -> Indexed i p (c, a) (c, b) #

newtype UnIndexed i p a b Source #

Constructors

UnIndexed (p a b) 

Instances

Instances details
Profunctor p => Indexable i (UnIndexed i p) p Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

indexed :: UnIndexed i p a b -> p (i, a) b Source #

Profunctor p => Profunctor (UnIndexed i p) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> UnIndexed i p b c -> UnIndexed i p a d #

lmap :: (a -> b) -> UnIndexed i p b c -> UnIndexed i p a c #

rmap :: (b -> c) -> UnIndexed i p a b -> UnIndexed i p a c #

(#.) :: forall a b c q. Coercible c b => q b c -> UnIndexed i p a b -> UnIndexed i p a c #

(.#) :: forall a b c q. Coercible b a => UnIndexed i p b c -> q a b -> UnIndexed i p a c #

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

Defined in Data.Profunctor.Indexed

Methods

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

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

Traversing p => Traversing (UnIndexed i p) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

traverse' :: Traversable f => UnIndexed i p a b -> UnIndexed i p (f a) (f b) #

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> UnIndexed i p a b -> UnIndexed i p s t #

Cochoice p => Cochoice (UnIndexed i p) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

unleft :: UnIndexed i p (Either a d) (Either b d) -> UnIndexed i p a b #

unright :: UnIndexed i p (Either d a) (Either d b) -> UnIndexed i p a b #

Closed p => Closed (UnIndexed i p) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

closed :: UnIndexed i p a b -> UnIndexed i p (x -> a) (x -> b) #

Strong p => Strong (UnIndexed i p) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: UnIndexed i p a b -> UnIndexed i p (a, c) (b, c) #

second' :: UnIndexed i p a b -> UnIndexed i p (c, a) (c, b) #

Costrong p => Costrong (UnIndexed i p) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

unfirst :: UnIndexed i p (a, d) (b, d) -> UnIndexed i p a b #

unsecond :: UnIndexed i p (d, a) (d, b) -> UnIndexed i p a b #