License | BSD-style (see the file LICENSE) |
---|---|
Maintainer | sjoerd@w3future.com |
Safe Haskell | Safe |
Language | Haskell2010 |
Documentation
data PList (ps :: [* -> * -> *]) (a :: *) (b :: *) where Source #
N-ary composition of profunctors.
Instances
(Profunctor p, Profunctor (PList (q ': qs))) => Profunctor (PList (p ': (q ': qs))) Source # | |
Defined in Data.Profunctor.Composition.List dimap :: (a -> b) -> (c -> d) -> PList (p ': (q ': qs)) b c -> PList (p ': (q ': qs)) a d # lmap :: (a -> b) -> PList (p ': (q ': qs)) b c -> PList (p ': (q ': qs)) a c # rmap :: (b -> c) -> PList (p ': (q ': qs)) a b -> PList (p ': (q ': qs)) a c # (#.) :: Coercible c b => q0 b c -> PList (p ': (q ': qs)) a b -> PList (p ': (q ': qs)) a c # (.#) :: Coercible b a => PList (p ': (q ': qs)) b c -> q0 a b -> PList (p ': (q ': qs)) a c # | |
Profunctor p => Profunctor (PList (p ': ([] :: [Type -> Type -> Type]))) Source # | |
Defined in Data.Profunctor.Composition.List dimap :: (a -> b) -> (c -> d) -> PList (p ': []) b c -> PList (p ': []) a d # lmap :: (a -> b) -> PList (p ': []) b c -> PList (p ': []) a c # rmap :: (b -> c) -> PList (p ': []) a b -> PList (p ': []) a c # (#.) :: Coercible c b => q b c -> PList (p ': []) a b -> PList (p ': []) a c # (.#) :: Coercible b a => PList (p ': []) b c -> q a b -> PList (p ': []) a c # | |
Profunctor (PList ([] :: [Type -> Type -> Type])) Source # | |
Defined in Data.Profunctor.Composition.List |
class PAppend p where Source #
Combining and splitting nested PList
s.
pappend :: Profunctor (PList q) => Procompose (PList q) (PList p) a b -> PList (p ++ q) a b Source #
punappend :: PList (p ++ q) a b -> Procompose (PList q) (PList p) a b Source #
Instances
PAppend ([] :: [Type -> Type -> Type]) Source # | |
Defined in Data.Profunctor.Composition.List | |
(Profunctor p, PAppend (q ': qs)) => PAppend (p ': (q ': qs)) Source # | |
Defined in Data.Profunctor.Composition.List | |
Profunctor p => PAppend (p ': ([] :: [Type -> Type -> Type])) Source # | |
Defined in Data.Profunctor.Composition.List |