Portability | Type-Families |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
- class (Functor (Rep p), Profunctor p) => Representable p where
- tabulated :: (Representable p, Representable q) => Iso (d -> Rep p c) (d' -> Rep q c') (p d c) (q d' c')
- class (Functor (Corep p), Profunctor p) => Corepresentable p where
- type Corep p :: * -> *
- cotabulate :: (Corep p d -> c) -> p d c
- corep :: p d c -> Corep p d -> c
- cotabulated :: (Corepresentable p, Corepresentable q) => Iso (Corep p d -> c) (Corep q d' -> c') (p d c) (q d' c')
Representable Profunctors
class (Functor (Rep p), Profunctor p) => Representable p whereSource
A Profunctor
p
is Representable
if there exists a Functor
f
such that
p d c
is isomorphic to d -> f c
.
Representable (->) | |
(Monad m, Functor m) => Representable (Kleisli m) | |
Functor f => Representable (UpStar f) | |
(Representable p, Representable q) => Representable (Procompose p q) | The composition of two |
tabulated :: (Representable p, Representable q) => Iso (d -> Rep p c) (d' -> Rep q c') (p d c) (q d' c')Source
tabulate
and rep
form two halves of an isomorphism.
This can be used with the combinators from the lens
package.
tabulated
::Representable
p =>Iso'
(d ->Rep
p c) (p d c)
Corepresentable Profunctors
class (Functor (Corep p), Profunctor p) => Corepresentable p whereSource
A Profunctor
p
is Corepresentable
if there exists a Functor
f
such that
p d c
is isomorphic to f d -> c
.
Corepresentable (->) | |
Functor w => Corepresentable (Cokleisli w) | |
Corepresentable (Tagged *) | |
Functor f => Corepresentable (DownStar f) | |
(Corepresentable p, Corepresentable q) => Corepresentable (Procompose p q) |
cotabulated :: (Corepresentable p, Corepresentable q) => Iso (Corep p d -> c) (Corep q d' -> c') (p d c) (q d' c')Source
cotabulate
and corep
form two halves of an isomorphism.
This can be used with the combinators from the lens
package.
tabulated
::Corep
f p =>Iso'
(f d -> c) (p d c)