#if __GLASGOW_HASKELL__ >= 702 && __GLASGOW_HASKELL__ <= 708
#endif
module Data.Profunctor.Rep
(
Representable(..)
, tabulated
, firstRep, secondRep
, Corepresentable(..)
, cotabulated
) where
import Control.Applicative
import Control.Arrow
import Control.Comonad
import Data.Functor.Identity
import Data.Profunctor
import Data.Profunctor.Sieve
import Data.Proxy
import Data.Tagged
class (Sieve p (Rep p), Strong p) => Representable p where
type Rep p :: * -> *
tabulate :: (d -> Rep p c) -> p d c
firstRep :: Representable p => p a b -> p (a, c) (b, c)
firstRep p = tabulate $ \(a,c) -> (\b -> (b, c)) <$> sieve p a
secondRep :: Representable p => p a b -> p (c, a) (c, b)
secondRep p = tabulate $ \(c,a) -> (,) c <$> sieve p a
instance Representable (->) where
type Rep (->) = Identity
tabulate f = runIdentity . f
instance (Monad m, Functor m) => Representable (Kleisli m) where
type Rep (Kleisli m) = m
tabulate = Kleisli
instance Functor f => Representable (Star f) where
type Rep (Star f) = f
tabulate = Star
instance Representable (Forget r) where
type Rep (Forget r) = Const r
tabulate = Forget . (getConst .)
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 sieve)
class Cosieve p (Corep p) => Corepresentable p where
type Corep p :: * -> *
cotabulate :: (Corep p d -> c) -> p d c
instance Corepresentable (->) where
type Corep (->) = Identity
cotabulate f = f . Identity
instance Functor w => Corepresentable (Cokleisli w) where
type Corep (Cokleisli w) = w
cotabulate = Cokleisli
instance Corepresentable Tagged where
type Corep Tagged = Proxy
cotabulate f = Tagged (f Proxy)
instance Functor f => Corepresentable (Costar f) where
type Corep (Costar f) = f
cotabulate = Costar
cotabulated :: (Corepresentable p, Corepresentable q) => Iso (Corep p d -> c) (Corep q d' -> c') (p d c) (q d' c')
cotabulated = dimap cotabulate (fmap cosieve)