License | BSD-style (see the file LICENSE) |
---|---|
Maintainer | sjoerd@w3future.com |
Safe Haskell | Safe-Inferred |
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 # (#.) :: forall a b c q0. Coercible c b => q0 b c -> PList (p ': (q ': qs)) a b -> PList (p ': (q ': qs)) a c # (.#) :: forall a b c q0. Coercible b a => PList (p ': (q ': qs)) b c -> q0 a b -> PList (p ': (q ': qs)) a c # | |
Profunctor p => Profunctor (PList '[p]) 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 # (#.) :: forall a b c q. Coercible c b => q b c -> PList '[p] a b -> PList '[p] a c # (.#) :: forall a b c q. 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 dimap :: (a -> b) -> (c -> d) -> PList '[] b c -> PList '[] a d # lmap :: (a -> b) -> PList '[] b c -> PList '[] a c # rmap :: (b -> c) -> PList '[] a b -> PList '[] a c # (#.) :: forall a b c q. Coercible c b => q b c -> PList '[] a b -> PList '[] a c # (.#) :: forall a b c q. Coercible b a => PList '[] b c -> q a b -> PList '[] a c # |
type family PlainP (ps :: [* -> * -> *]) :: * -> * -> * Source #
Calculate the simplified type of the composition of a list of profunctors.
class IsPList ps where Source #
Functions for working with PList
s.
pappend :: (Profunctor (PList ps), Profunctor (PList qs)) => Procompose (PList qs) (PList ps) :-> PList (ps ++ qs) Source #
punappend :: PList (ps ++ qs) :-> Procompose (PList qs) (PList ps) Source #
toPlainP :: PList ps :-> PlainP ps Source #
Convert a PList
to its simplified form.
fromPlainP :: PlainP ps :-> PList ps Source #
Create a PList
from its simplified form.
Instances
IsPList ('[] :: [Type -> Type -> Type]) Source # | |
Defined in Data.Profunctor.Composition.List pappend :: forall (qs :: [Type -> Type -> Type]). (Profunctor (PList '[]), Profunctor (PList qs)) => Procompose (PList qs) (PList '[]) :-> PList ('[] ++ qs) Source # punappend :: forall (qs :: [Type -> Type -> Type]). PList ('[] ++ qs) :-> Procompose (PList qs) (PList '[]) Source # | |
(Profunctor (PList (q ': qs)), IsPList (q ': qs)) => IsPList (p ': (q ': qs)) Source # | |
Defined in Data.Profunctor.Composition.List pappend :: forall (qs0 :: [Type -> Type -> Type]). (Profunctor (PList (p ': (q ': qs))), Profunctor (PList qs0)) => Procompose (PList qs0) (PList (p ': (q ': qs))) :-> PList ((p ': (q ': qs)) ++ qs0) Source # punappend :: forall (qs0 :: [Type -> Type -> Type]). PList ((p ': (q ': qs)) ++ qs0) :-> Procompose (PList qs0) (PList (p ': (q ': qs))) Source # toPlainP :: PList (p ': (q ': qs)) :-> PlainP (p ': (q ': qs)) Source # fromPlainP :: PlainP (p ': (q ': qs)) :-> PList (p ': (q ': qs)) Source # | |
IsPList '[p] Source # | |
Defined in Data.Profunctor.Composition.List pappend :: forall (qs :: [Type -> Type -> Type]). (Profunctor (PList '[p]), Profunctor (PList qs)) => Procompose (PList qs) (PList '[p]) :-> PList ('[p] ++ qs) Source # punappend :: forall (qs :: [Type -> Type -> Type]). PList ('[p] ++ qs) :-> Procompose (PList qs) (PList '[p]) Source # |