{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fenable-rewrite-rules #-}
module Data.Functor.Rep
(
Representable(..)
, tabulated
, Co(..)
, fmapRep
, distributeRep
, collectRep
, apRep
, pureRep
, liftR2
, liftR3
, bindRep
, mfixRep
, mzipRep
, mzipWithRep
, askRep
, localRep
, duplicatedRep
, extendedRep
, duplicateRep
, extendRep
, extractRep
, duplicateRepBy
, extendRepBy
, extractRepBy
, imapRep
, ifoldMapRep
, itraverseRep
, GRep
, gindex
, gtabulate
, WrappedRep(..)
) where
import Control.Applicative
import Control.Applicative.Backwards
import Control.Arrow ((&&&))
#if __GLASGOW_HASKELL__ >= 708
import Data.Coerce
#endif
import Control.Comonad
import Control.Comonad.Trans.Class
import Control.Comonad.Trans.Traced
import Control.Comonad.Cofree
import Control.Monad.Fix (MonadFix(..))
import Control.Monad.Trans.Identity
import Control.Monad.Reader (MonadReader(..), ReaderT(..))
#if MIN_VERSION_base(4,4,0)
import Data.Complex
#endif
import Data.Distributive
import Data.Foldable (Foldable(fold))
import Data.Function
import Data.Functor.Bind
import Data.Functor.Identity
import Data.Functor.Compose
import Data.Functor.Extend
import Data.Functor.Product
import Data.Functor.Reverse
import qualified Data.Monoid as Monoid
import Data.Profunctor.Unsafe
import Data.Proxy
import Data.Sequence (Seq)
import qualified Data.Sequence as Seq
import Data.Semigroup hiding (Product)
import Data.Tagged
#if !(MIN_VERSION_base(4,8,0))
import Data.Traversable (Traversable(sequenceA))
#endif
import Data.Void
import GHC.Generics hiding (Rep)
import Prelude hiding (lookup)
class Distributive f => Representable f where
type Rep f :: *
type Rep f = GRep f
tabulate :: (Rep f -> a) -> f a
default tabulate :: (Generic1 f, GRep f ~ Rep f, GTabulate (Rep1 f))
=> (Rep f -> a) -> f a
tabulate = forall (f :: * -> *) a.
(Generic1 f, GRep f ~ Rep f, GTabulate (Rep1 f)) =>
(Rep f -> a) -> f a
gtabulate
index :: f a -> Rep f -> a
default index :: (Generic1 f, GRep f ~ Rep f, GIndex (Rep1 f))
=> f a -> Rep f -> a
index = forall (f :: * -> *) a.
(Generic1 f, GRep f ~ Rep f, GIndex (Rep1 f)) =>
f a -> Rep f -> a
gindex
type GRep f = GRep' (Rep1 f)
gtabulate :: (Generic1 f, GRep f ~ Rep f, GTabulate (Rep1 f))
=> (Rep f -> a) -> f a
gtabulate :: forall (f :: * -> *) a.
(Generic1 f, GRep f ~ Rep f, GTabulate (Rep1 f)) =>
(Rep f -> a) -> f a
gtabulate = forall k (f :: k -> *) (a :: k). Generic1 f => Rep1 f a -> f a
to1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. GTabulate f => (GRep' f -> a) -> f a
gtabulate'
gindex :: (Generic1 f, GRep f ~ Rep f, GIndex (Rep1 f))
=> f a -> Rep f -> a
gindex :: forall (f :: * -> *) a.
(Generic1 f, GRep f ~ Rep f, GIndex (Rep1 f)) =>
f a -> Rep f -> a
gindex = forall (f :: * -> *) a. GIndex f => f a -> GRep' f -> a
gindex' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k (f :: k -> *) (a :: k). Generic1 f => f a -> Rep1 f a
from1
type family GRep' (f :: * -> *) :: *
class GTabulate f where
gtabulate' :: (GRep' f -> a) -> f a
class GIndex f where
gindex' :: f a -> GRep' f -> a
type instance GRep' (f :*: g) = Either (GRep' f) (GRep' g)
instance (GTabulate f, GTabulate g) => GTabulate (f :*: g) where
gtabulate' :: forall a. (GRep' (f :*: g) -> a) -> (:*:) f g a
gtabulate' GRep' (f :*: g) -> a
f = forall (f :: * -> *) a. GTabulate f => (GRep' f -> a) -> f a
gtabulate' (GRep' (f :*: g) -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left) forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: forall (f :: * -> *) a. GTabulate f => (GRep' f -> a) -> f a
gtabulate' (GRep' (f :*: g) -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right)
instance (GIndex f, GIndex g) => GIndex (f :*: g) where
gindex' :: forall a. (:*:) f g a -> GRep' (f :*: g) -> a
gindex' (f a
a :*: g a
_) (Left GRep' f
i) = forall (f :: * -> *) a. GIndex f => f a -> GRep' f -> a
gindex' f a
a GRep' f
i
gindex' (f a
_ :*: g a
b) (Right GRep' g
j) = forall (f :: * -> *) a. GIndex f => f a -> GRep' f -> a
gindex' g a
b GRep' g
j
type instance GRep' (f :.: g) = (WrappedRep f, GRep' g)
instance (Representable f, GTabulate g) => GTabulate (f :.: g) where
gtabulate' :: forall a. (GRep' (f :.: g) -> a) -> (:.:) f g a
gtabulate' GRep' (f :.: g) -> a
f = forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Comp1 forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (f :: * -> *) a. GTabulate f => (GRep' f -> a) -> f a
gtabulate' forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b c. ((a, b) -> c) -> a -> b -> c
curry GRep' (f :.: g) -> a
f) forall (f :: * -> *). Rep f -> WrappedRep f
WrapRep
instance (Representable f, GIndex g) => GIndex (f :.: g) where
gindex' :: forall a. (:.:) f g a -> GRep' (f :.: g) -> a
gindex' (Comp1 f (g a)
fg) (WrappedRep f
i, GRep' g
j) = forall (f :: * -> *) a. GIndex f => f a -> GRep' f -> a
gindex' (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f (g a)
fg (forall (f :: * -> *). WrappedRep f -> Rep f
unwrapRep WrappedRep f
i)) GRep' g
j
type instance GRep' Par1 = ()
instance GTabulate Par1 where
gtabulate' :: forall a. (GRep' Par1 -> a) -> Par1 a
gtabulate' GRep' Par1 -> a
f = forall p. p -> Par1 p
Par1 (GRep' Par1 -> a
f ())
instance GIndex Par1 where
gindex' :: forall a. Par1 a -> GRep' Par1 -> a
gindex' (Par1 a
a) () = a
a
type instance GRep' (Rec1 f) = WrappedRep f
#if __GLASGOW_HASKELL__ >= 708
instance Representable f => GTabulate (Rec1 f) where
gtabulate' :: forall a. (GRep' (Rec1 f) -> a) -> Rec1 f a
gtabulate' = coerce :: forall a b. Coercible a b => a -> b
coerce (forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate :: (Rep f -> a) -> f a)
:: forall a . (WrappedRep f -> a) -> Rec1 f a
instance Representable f => GIndex (Rec1 f) where
gindex' :: forall a. Rec1 f a -> GRep' (Rec1 f) -> a
gindex' = coerce :: forall a b. Coercible a b => a -> b
coerce (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index :: f a -> Rep f -> a)
:: forall a . Rec1 f a -> WrappedRep f -> a
#else
instance Representable f => GTabulate (Rec1 f) where
gtabulate' = Rec1 #. tabulate .# (. WrapRep)
instance Representable f => GIndex (Rec1 f) where
gindex' = (. unwrapRep) #. index .# unRec1
#endif
type instance GRep' (M1 i c f) = GRep' f
instance GTabulate f => GTabulate (M1 i c f) where
gtabulate' :: forall a. (GRep' (M1 i c f) -> a) -> M1 i c f a
gtabulate' = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. forall (f :: * -> *) a. GTabulate f => (GRep' f -> a) -> f a
gtabulate'
instance GIndex f => GIndex (M1 i c f) where
gindex' :: forall a. M1 i c f a -> GRep' (M1 i c f) -> a
gindex' = forall (f :: * -> *) a. GIndex f => f a -> GRep' f -> a
gindex' forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# forall k i (c :: Meta) (f :: k -> *) (p :: k). M1 i c f p -> f p
unM1
newtype WrappedRep f = WrapRep { forall (f :: * -> *). WrappedRep f -> Rep f
unwrapRep :: Rep f }
{-# RULES
"tabulate/index" forall t. tabulate (index t) = t #-}
tabulated :: (Representable f, Representable g, Profunctor p, Functor h)
=> p (f a) (h (g b)) -> p (Rep f -> a) (h (Rep g -> b))
tabulated :: forall (f :: * -> *) (g :: * -> *) (p :: * -> * -> *) (h :: * -> *)
a b.
(Representable f, Representable g, Profunctor p, Functor h) =>
p (f a) (h (g b)) -> p (Rep f -> a) (h (Rep g -> b))
tabulated = forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index)
{-# INLINE tabulated #-}
fmapRep :: Representable f => (a -> b) -> f a -> f b
fmapRep :: forall (f :: * -> *) a b. Representable f => (a -> b) -> f a -> f b
fmapRep a -> b
f = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index
pureRep :: Representable f => a -> f a
pureRep :: forall (f :: * -> *) a. Representable f => a -> f a
pureRep = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const
bindRep :: Representable f => f a -> (a -> f b) -> f b
bindRep :: forall (f :: * -> *) a b.
Representable f =>
f a -> (a -> f b) -> f b
bindRep f a
m a -> f b
f = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall a b. (a -> b) -> a -> b
$ \Rep f
a -> forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (a -> f b
f (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
m Rep f
a)) Rep f
a
mfixRep :: Representable f => (a -> f a) -> f a
mfixRep :: forall (f :: * -> *) a. Representable f => (a -> f a) -> f a
mfixRep = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadFix m => (a -> m a) -> m a
mfix forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index
mzipWithRep :: Representable f => (a -> b -> c) -> f a -> f b -> f c
mzipWithRep :: forall (f :: * -> *) a b c.
Representable f =>
(a -> b -> c) -> f a -> f b -> f c
mzipWithRep a -> b -> c
f f a
as f b
bs = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall a b. (a -> b) -> a -> b
$ \Rep f
k -> a -> b -> c
f (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
as Rep f
k) (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f b
bs Rep f
k)
mzipRep :: Representable f => f a -> f b -> f (a, b)
mzipRep :: forall (f :: * -> *) a b. Representable f => f a -> f b -> f (a, b)
mzipRep f a
as f b
bs = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
as forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f b
bs)
askRep :: Representable f => f (Rep f)
askRep :: forall (f :: * -> *). Representable f => f (Rep f)
askRep = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall a. a -> a
id
localRep :: Representable f => (Rep f -> Rep f) -> f a -> f a
localRep :: forall (f :: * -> *) a.
Representable f =>
(Rep f -> Rep f) -> f a -> f a
localRep Rep f -> Rep f
f f a
m = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
m forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rep f -> Rep f
f)
apRep :: Representable f => f (a -> b) -> f a -> f b
apRep :: forall (f :: * -> *) a b.
Representable f =>
f (a -> b) -> f a -> f b
apRep f (a -> b)
f f a
g = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f (a -> b)
f forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
g)
distributeRep :: (Representable f, Functor w) => w (f a) -> f (w a)
distributeRep :: forall (f :: * -> *) (w :: * -> *) a.
(Representable f, Functor w) =>
w (f a) -> f (w a)
distributeRep w (f a)
wf = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (\Rep f
k -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
`index` Rep f
k) w (f a)
wf)
collectRep :: (Representable f, Functor w) => (a -> f b) -> w a -> f (w b)
collectRep :: forall (f :: * -> *) (w :: * -> *) a b.
(Representable f, Functor w) =>
(a -> f b) -> w a -> f (w b)
collectRep a -> f b
f w a
w = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (\Rep f
k -> (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
`index` Rep f
k) forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> f b
f forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> w a
w)
duplicateRepBy :: Representable f => (Rep f -> Rep f -> Rep f) -> f a -> f (f a)
duplicateRepBy :: forall (f :: * -> *) a.
Representable f =>
(Rep f -> Rep f -> Rep f) -> f a -> f (f a)
duplicateRepBy Rep f -> Rep f -> Rep f
plus f a
w = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (\Rep f
m -> forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
w forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rep f -> Rep f -> Rep f
plus Rep f
m))
extendRepBy :: Representable f => (Rep f -> Rep f -> Rep f) -> (f a -> b) -> f a -> f b
extendRepBy :: forall (f :: * -> *) a b.
Representable f =>
(Rep f -> Rep f -> Rep f) -> (f a -> b) -> f a -> f b
extendRepBy Rep f -> Rep f -> Rep f
plus f a -> b
f f a
w = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (\Rep f
m -> f a -> b
f (forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
w forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rep f -> Rep f -> Rep f
plus Rep f
m)))
extractRepBy :: Representable f => (Rep f) -> f a -> a
= forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index
duplicatedRep :: (Representable f, Semigroup (Rep f)) => f a -> f (f a)
duplicatedRep :: forall (f :: * -> *) a.
(Representable f, Semigroup (Rep f)) =>
f a -> f (f a)
duplicatedRep = forall (f :: * -> *) a.
Representable f =>
(Rep f -> Rep f -> Rep f) -> f a -> f (f a)
duplicateRepBy forall a. Semigroup a => a -> a -> a
(<>)
extendedRep :: (Representable f, Semigroup (Rep f)) => (f a -> b) -> f a -> f b
extendedRep :: forall (f :: * -> *) a b.
(Representable f, Semigroup (Rep f)) =>
(f a -> b) -> f a -> f b
extendedRep = forall (f :: * -> *) a b.
Representable f =>
(Rep f -> Rep f -> Rep f) -> (f a -> b) -> f a -> f b
extendRepBy forall a. Semigroup a => a -> a -> a
(<>)
duplicateRep :: (Representable f, Monoid (Rep f)) => f a -> f (f a)
duplicateRep :: forall (f :: * -> *) a.
(Representable f, Monoid (Rep f)) =>
f a -> f (f a)
duplicateRep = forall (f :: * -> *) a.
Representable f =>
(Rep f -> Rep f -> Rep f) -> f a -> f (f a)
duplicateRepBy forall a. Monoid a => a -> a -> a
mappend
extendRep :: (Representable f, Monoid (Rep f)) => (f a -> b) -> f a -> f b
extendRep :: forall (f :: * -> *) a b.
(Representable f, Monoid (Rep f)) =>
(f a -> b) -> f a -> f b
extendRep = forall (f :: * -> *) a b.
Representable f =>
(Rep f -> Rep f -> Rep f) -> (f a -> b) -> f a -> f b
extendRepBy forall a. Monoid a => a -> a -> a
mappend
extractRep :: (Representable f, Monoid (Rep f)) => f a -> a
= forall (f :: * -> *) a. Representable f => Rep f -> f a -> a
extractRepBy forall a. Monoid a => a
mempty
imapRep :: Representable r => (Rep r -> a -> a') -> (r a -> r a')
imapRep :: forall (r :: * -> *) a a'.
Representable r =>
(Rep r -> a -> a') -> r a -> r a'
imapRep Rep r -> a -> a'
f r a
xs = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Rep r -> a -> a'
f forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index r a
xs)
ifoldMapRep :: forall r m a. (Representable r, Foldable r, Monoid m)
=> (Rep r -> a -> m) -> (r a -> m)
ifoldMapRep :: forall (r :: * -> *) m a.
(Representable r, Foldable r, Monoid m) =>
(Rep r -> a -> m) -> r a -> m
ifoldMapRep Rep r -> a -> m
ix r a
xs = forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold (forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (\(Rep r
i :: Rep r) -> Rep r -> a -> m
ix Rep r
i forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index r a
xs Rep r
i) :: r m)
itraverseRep :: forall r f a a'. (Representable r, Traversable r, Applicative f)
=> (Rep r -> a -> f a') -> (r a -> f (r a'))
itraverseRep :: forall (r :: * -> *) (f :: * -> *) a a'.
(Representable r, Traversable r, Applicative f) =>
(Rep r -> a -> f a') -> r a -> f (r a')
itraverseRep Rep r -> a -> f a'
ix r a
xs = forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Rep r -> a -> f a'
ix forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index r a
xs)
instance Representable Proxy where
type Rep Proxy = Void
index :: forall a. Proxy a -> Rep Proxy -> a
index Proxy a
Proxy = forall a. Void -> a
absurd
tabulate :: forall a. (Rep Proxy -> a) -> Proxy a
tabulate Rep Proxy -> a
_ = forall {k} (t :: k). Proxy t
Proxy
instance Representable Identity where
type Rep Identity = ()
index :: forall a. Identity a -> Rep Identity -> a
index (Identity a
a) () = a
a
tabulate :: forall a. (Rep Identity -> a) -> Identity a
tabulate Rep Identity -> a
f = forall a. a -> Identity a
Identity (Rep Identity -> a
f ())
instance Representable (Tagged t) where
type Rep (Tagged t) = ()
index :: forall a. Tagged t a -> Rep (Tagged t) -> a
index (Tagged a
a) () = a
a
tabulate :: forall a. (Rep (Tagged t) -> a) -> Tagged t a
tabulate Rep (Tagged t) -> a
f = forall {k} (s :: k) b. b -> Tagged s b
Tagged (Rep (Tagged t) -> a
f ())
instance Representable m => Representable (IdentityT m) where
type Rep (IdentityT m) = Rep m
index :: forall a. IdentityT m a -> Rep (IdentityT m) -> a
index = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT
tabulate :: forall a. (Rep (IdentityT m) -> a) -> IdentityT m a
tabulate = forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate
instance Representable ((->) e) where
type Rep ((->) e) = e
index :: forall a. (e -> a) -> Rep ((->) e) -> a
index = forall a. a -> a
id
tabulate :: forall a. (Rep ((->) e) -> a) -> e -> a
tabulate = forall a. a -> a
id
instance Representable m => Representable (ReaderT e m) where
type Rep (ReaderT e m) = (e, Rep m)
index :: forall a. ReaderT e m a -> Rep (ReaderT e m) -> a
index (ReaderT e -> m a
f) (e
e,Rep m
k) = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (e -> m a
f e
e) Rep m
k
tabulate :: forall a. (Rep (ReaderT e m) -> a) -> ReaderT e m a
tabulate = forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. ((a, b) -> c) -> a -> b -> c
curry
instance (Representable f, Representable g) => Representable (Compose f g) where
type Rep (Compose f g) = (Rep f, Rep g)
index :: forall a. Compose f g a -> Rep (Compose f g) -> a
index (Compose f (g a)
fg) (Rep f
i,Rep g
j) = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f (g a)
fg Rep f
i) Rep g
j
tabulate :: forall a. (Rep (Compose f g) -> a) -> Compose f g a
tabulate = forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. ((a, b) -> c) -> a -> b -> c
curry
instance Representable w => Representable (TracedT s w) where
type Rep (TracedT s w) = (s, Rep w)
index :: forall a. TracedT s w a -> Rep (TracedT s w) -> a
index (TracedT w (s -> a)
w) (s
e,Rep w
k) = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index w (s -> a)
w Rep w
k s
e
tabulate :: forall a. (Rep (TracedT s w) -> a) -> TracedT s w a
tabulate = forall m (w :: * -> *) a. w (m -> a) -> TracedT m w a
TracedT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Co f a -> f a
unCo forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (g :: * -> *) (f :: * -> *) a b.
(Distributive g, Functor f) =>
(a -> g b) -> f a -> g (f b)
collect (forall (f :: * -> *) a. f a -> Co f a
Co forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. ((a, b) -> c) -> a -> b -> c
curry
instance (Representable f, Representable g) => Representable (Product f g) where
type Rep (Product f g) = Either (Rep f) (Rep g)
index :: forall a. Product f g a -> Rep (Product f g) -> a
index (Pair f a
a g a
_) (Left Rep f
i) = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
a Rep f
i
index (Pair f a
_ g a
b) (Right Rep g
j) = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index g a
b Rep g
j
tabulate :: forall a. (Rep (Product f g) -> a) -> Product f g a
tabulate Rep (Product f g) -> a
f = forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair (forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Rep (Product f g) -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left)) (forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Rep (Product f g) -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right))
instance Representable f => Representable (Cofree f) where
type Rep (Cofree f) = Seq (Rep f)
index :: forall a. Cofree f a -> Rep (Cofree f) -> a
index (a
a :< f (Cofree f a)
as) Rep (Cofree f)
key = case forall a. Seq a -> ViewL a
Seq.viewl Rep (Cofree f)
key of
ViewL (Rep f)
Seq.EmptyL -> a
a
Rep f
k Seq.:< Seq (Rep f)
ks -> forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f (Cofree f a)
as Rep f
k) Seq (Rep f)
ks
tabulate :: forall a. (Rep (Cofree f) -> a) -> Cofree f a
tabulate Rep (Cofree f) -> a
f = Rep (Cofree f) -> a
f forall a. Seq a
Seq.empty forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (\Rep f
k -> forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Rep (Cofree f) -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rep f
k forall a. a -> Seq a -> Seq a
Seq.<|)))
instance Representable f => Representable (Backwards f) where
type Rep (Backwards f) = Rep f
index :: forall a. Backwards f a -> Rep (Backwards f) -> a
index = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# forall {k} (f :: k -> *) (a :: k). Backwards f a -> f a
forwards
tabulate :: forall a. (Rep (Backwards f) -> a) -> Backwards f a
tabulate = forall {k} (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate
instance Representable f => Representable (Reverse f) where
type Rep (Reverse f) = Rep f
index :: forall a. Reverse f a -> Rep (Reverse f) -> a
index = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# forall {k} (f :: k -> *) (a :: k). Reverse f a -> f a
getReverse
tabulate :: forall a. (Rep (Reverse f) -> a) -> Reverse f a
tabulate = forall {k} (f :: k -> *) (a :: k). f a -> Reverse f a
Reverse forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate
instance Representable Monoid.Dual where
type Rep Monoid.Dual = ()
index :: forall a. Dual a -> Rep Dual -> a
index (Monoid.Dual a
d) () = a
d
tabulate :: forall a. (Rep Dual -> a) -> Dual a
tabulate Rep Dual -> a
f = forall a. a -> Dual a
Monoid.Dual (Rep Dual -> a
f ())
instance Representable Monoid.Product where
type Rep Monoid.Product = ()
index :: forall a. Product a -> Rep Product -> a
index (Monoid.Product a
p) () = a
p
tabulate :: forall a. (Rep Product -> a) -> Product a
tabulate Rep Product -> a
f = forall a. a -> Product a
Monoid.Product (Rep Product -> a
f ())
instance Representable Monoid.Sum where
type Rep Monoid.Sum = ()
index :: forall a. Sum a -> Rep Sum -> a
index (Monoid.Sum a
s) () = a
s
tabulate :: forall a. (Rep Sum -> a) -> Sum a
tabulate Rep Sum -> a
f = forall a. a -> Sum a
Monoid.Sum (Rep Sum -> a
f ())
#if MIN_VERSION_base(4,4,0)
instance Representable Complex where
type Rep Complex = Bool
index :: forall a. Complex a -> Rep Complex -> a
index (a
r :+ a
i) Rep Complex
key = if Rep Complex
key then a
i else a
r
tabulate :: forall a. (Rep Complex -> a) -> Complex a
tabulate Rep Complex -> a
f = Rep Complex -> a
f Bool
False forall a. a -> a -> Complex a
:+ Rep Complex -> a
f Bool
True
#endif
instance Representable U1 where
type Rep U1 = Void
index :: forall a. U1 a -> Rep U1 -> a
index U1 a
U1 = forall a. Void -> a
absurd
tabulate :: forall a. (Rep U1 -> a) -> U1 a
tabulate Rep U1 -> a
_ = forall k (p :: k). U1 p
U1
instance (Representable f, Representable g) => Representable (f :*: g) where
type Rep (f :*: g) = Either (Rep f) (Rep g)
index :: forall a. (:*:) f g a -> Rep (f :*: g) -> a
index (f a
a :*: g a
_) (Left Rep f
i) = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
a Rep f
i
index (f a
_ :*: g a
b) (Right Rep g
j) = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index g a
b Rep g
j
tabulate :: forall a. (Rep (f :*: g) -> a) -> (:*:) f g a
tabulate Rep (f :*: g) -> a
f = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Rep (f :*: g) -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left) forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Rep (f :*: g) -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right)
instance (Representable f, Representable g) => Representable (f :.: g) where
type Rep (f :.: g) = (Rep f, Rep g)
index :: forall a. (:.:) f g a -> Rep (f :.: g) -> a
index (Comp1 f (g a)
fg) (Rep f
i, Rep g
j) = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f (g a)
fg Rep f
i) Rep g
j
tabulate :: forall a. (Rep (f :.: g) -> a) -> (:.:) f g a
tabulate = forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Comp1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. ((a, b) -> c) -> a -> b -> c
curry
instance Representable Par1 where
type Rep Par1 = ()
index :: forall a. Par1 a -> Rep Par1 -> a
index (Par1 a
a) () = a
a
tabulate :: forall a. (Rep Par1 -> a) -> Par1 a
tabulate Rep Par1 -> a
f = forall p. p -> Par1 p
Par1 (Rep Par1 -> a
f ())
instance Representable f => Representable (Rec1 f) where
type Rep (Rec1 f) = Rep f
index :: forall a. Rec1 f a -> Rep (Rec1 f) -> a
index = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# forall k (f :: k -> *) (p :: k). Rec1 f p -> f p
unRec1
tabulate :: forall a. (Rep (Rec1 f) -> a) -> Rec1 f a
tabulate = forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Rec1 forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate
instance Representable f => Representable (M1 i c f) where
type Rep (M1 i c f) = Rep f
index :: forall a. M1 i c f a -> Rep (M1 i c f) -> a
index = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# forall k i (c :: Meta) (f :: k -> *) (p :: k). M1 i c f p -> f p
unM1
tabulate :: forall a. (Rep (M1 i c f) -> a) -> M1 i c f a
tabulate = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate
newtype Co f a = Co { forall (f :: * -> *) a. Co f a -> f a
unCo :: f a } deriving forall a b. a -> Co f b -> Co f a
forall a b. (a -> b) -> Co f a -> Co f b
forall (f :: * -> *) a b. Functor f => a -> Co f b -> Co f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> Co f a -> Co f b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Co f b -> Co f a
$c<$ :: forall (f :: * -> *) a b. Functor f => a -> Co f b -> Co f a
fmap :: forall a b. (a -> b) -> Co f a -> Co f b
$cfmap :: forall (f :: * -> *) a b. Functor f => (a -> b) -> Co f a -> Co f b
Functor
instance Representable f => Representable (Co f) where
type Rep (Co f) = Rep f
tabulate :: forall a. (Rep (Co f) -> a) -> Co f a
tabulate = forall (f :: * -> *) a. f a -> Co f a
Co forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate
index :: forall a. Co f a -> Rep (Co f) -> a
index = forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# forall (f :: * -> *) a. Co f a -> f a
unCo
instance Representable f => Apply (Co f) where
<.> :: forall a b. Co f (a -> b) -> Co f a -> Co f b
(<.>) = forall (f :: * -> *) a b.
Representable f =>
f (a -> b) -> f a -> f b
apRep
instance Representable f => Applicative (Co f) where
pure :: forall a. a -> Co f a
pure = forall (f :: * -> *) a. Representable f => a -> f a
pureRep
<*> :: forall a b. Co f (a -> b) -> Co f a -> Co f b
(<*>) = forall (f :: * -> *) a b.
Representable f =>
f (a -> b) -> f a -> f b
apRep
instance Representable f => Distributive (Co f) where
distribute :: forall (f :: * -> *) a. Functor f => f (Co f a) -> Co f (f a)
distribute = forall (f :: * -> *) (w :: * -> *) a.
(Representable f, Functor w) =>
w (f a) -> f (w a)
distributeRep
collect :: forall (f :: * -> *) a b.
Functor f =>
(a -> Co f b) -> f a -> Co f (f b)
collect = forall (f :: * -> *) (w :: * -> *) a b.
(Representable f, Functor w) =>
(a -> f b) -> w a -> f (w b)
collectRep
instance Representable f => Bind (Co f) where
>>- :: forall a b. Co f a -> (a -> Co f b) -> Co f b
(>>-) = forall (f :: * -> *) a b.
Representable f =>
f a -> (a -> f b) -> f b
bindRep
instance Representable f => Monad (Co f) where
return :: forall a. a -> Co f a
return = forall (f :: * -> *) a. Applicative f => a -> f a
pure
>>= :: forall a b. Co f a -> (a -> Co f b) -> Co f b
(>>=) = forall (f :: * -> *) a b.
Representable f =>
f a -> (a -> f b) -> f b
bindRep
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 704
instance (Representable f, Rep f ~ a) => MonadReader a (Co f) where
ask :: Co f a
ask = forall (f :: * -> *). Representable f => f (Rep f)
askRep
local :: forall a. (a -> a) -> Co f a -> Co f a
local = forall (f :: * -> *) a.
Representable f =>
(Rep f -> Rep f) -> f a -> f a
localRep
#endif
instance (Representable f, Semigroup (Rep f)) => Extend (Co f) where
extended :: forall a b. (Co f a -> b) -> Co f a -> Co f b
extended = forall (f :: * -> *) a b.
(Representable f, Semigroup (Rep f)) =>
(f a -> b) -> f a -> f b
extendedRep
instance (Representable f, Monoid (Rep f)) => Comonad (Co f) where
extend :: forall a b. (Co f a -> b) -> Co f a -> Co f b
extend = forall (f :: * -> *) a b.
(Representable f, Monoid (Rep f)) =>
(f a -> b) -> f a -> f b
extendRep
extract :: forall a. Co f a -> a
extract = forall (f :: * -> *) a.
(Representable f, Monoid (Rep f)) =>
f a -> a
extractRep
instance ComonadTrans Co where
lower :: forall (w :: * -> *) a. Comonad w => Co w a -> w a
lower (Co w a
f) = w a
f
liftR2 :: Representable f => (a -> b -> c) -> f a -> f b -> f c
liftR2 :: forall (f :: * -> *) a b c.
Representable f =>
(a -> b -> c) -> f a -> f b -> f c
liftR2 a -> b -> c
f f a
fa f b
fb = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall a b. (a -> b) -> a -> b
$ \Rep f
i -> a -> b -> c
f (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
fa Rep f
i) (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f b
fb Rep f
i)
liftR3 :: Representable f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftR3 :: forall (f :: * -> *) a b c d.
Representable f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftR3 a -> b -> c -> d
f f a
fa f b
fb f c
fc = forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate forall a b. (a -> b) -> a -> b
$ \Rep f
i -> a -> b -> c -> d
f (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
fa Rep f
i) (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f b
fb Rep f
i) (forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f c
fc Rep f
i)