| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Profunctor.Indexed
Documentation
class (Profunctor p, Profunctor q) => Indexable i p q | p -> q where Source #
Minimal complete definition
Nothing
Methods
Instances
| Indexable i (Tagged :: Type -> Type -> Type) (Tagged :: Type -> Type -> Type) Source # | |
| Functor f => Indexable i (Costar f) (Costar f) Source # | |
| Functor f => Indexable i (Star f) (Star f) Source # | |
| Indexable i (Forget r) (Forget r) Source # | |
| Profunctor p => Indexable i (UnIndexed i p) p Source # | |
Defined in Data.Profunctor.Indexed | |
| Profunctor p => Indexable i (Indexed i p) p Source # | |
Defined in Data.Profunctor.Indexed | |
| Indexable i ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Data.Profunctor.Indexed | |
Constructors
| Indexed (p (i, a) b) |
Instances
| Profunctor p => Indexable i (Indexed i p) p Source # | |
Defined in Data.Profunctor.Indexed | |
| Profunctor p => Profunctor (Indexed i p) Source # | |
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 # | |
newtype UnIndexed i p a b Source #
Constructors
| UnIndexed (p a b) |
Instances
| Profunctor p => Indexable i (UnIndexed i p) p Source # | |
Defined in Data.Profunctor.Indexed | |
| Profunctor p => Profunctor (UnIndexed i p) Source # | |
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 # | |
| Traversing p => Traversing (UnIndexed i p) Source # | |
Defined in Data.Profunctor.Indexed | |
| Cochoice p => Cochoice (UnIndexed i p) Source # | |
| Closed p => Closed (UnIndexed i p) Source # | |
Defined in Data.Profunctor.Indexed | |
| Strong p => Strong (UnIndexed i p) Source # | |
| Costrong p => Costrong (UnIndexed i p) Source # | |