#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
#endif
module Data.Profunctor.Rep
(
Representable(..), tabulated
, Corepresentable(..), cotabulated
) where
import Control.Arrow
import Control.Comonad
import Data.Functor.Identity
import Data.Profunctor
import Data.Proxy
import Data.Tagged
class (Functor (Rep p), Profunctor p) => Representable p where
type Rep p :: * -> *
tabulate :: (d -> Rep p c) -> p d c
rep :: p d c -> d -> Rep p c
instance Representable (->) where
type Rep (->) = Identity
tabulate f = runIdentity . f
rep f = Identity . f
instance (Monad m, Functor m) => Representable (Kleisli m) where
type Rep (Kleisli m) = m
tabulate = Kleisli
rep = runKleisli
instance Functor f => Representable (UpStar f) where
type Rep (UpStar f) = f
tabulate = UpStar
rep = runUpStar
type Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t)
tabulated :: (Representable p, Representable q) => Iso (d -> Rep p c) (d' -> Rep q c') (p d c) (q d' c')
tabulated = dimap tabulate (fmap rep)
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
instance Corepresentable (->) where
type Corep (->) = Identity
cotabulate f = f . Identity
corep f (Identity d) = f d
instance Functor w => Corepresentable (Cokleisli w) where
type Corep (Cokleisli w) = w
cotabulate = Cokleisli
corep = runCokleisli
instance Corepresentable Tagged where
type Corep Tagged = Proxy
cotabulate f = Tagged (f Proxy)
corep (Tagged a) _ = a
instance Functor f => Corepresentable (DownStar f) where
type Corep (DownStar f) = f
cotabulate = DownStar
corep = runDownStar
cotabulated :: (Corepresentable p, Corepresentable q) => Iso (Corep p d -> c) (Corep q d' -> c') (p d c) (q d' c')
cotabulated = dimap cotabulate (fmap corep)