{-# 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 = (Rep f -> a) -> f a
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 = f a -> Rep f -> a
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 :: (Rep f -> a) -> f a
gtabulate = Rep1 f a -> f a
forall k (f :: k -> *) (a :: k). Generic1 f => Rep1 f a -> f a
to1 (Rep1 f a -> f a)
-> ((Rep f -> a) -> Rep1 f a) -> (Rep f -> a) -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rep f -> a) -> Rep1 f a
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 :: f a -> Rep f -> a
gindex = Rep1 f a -> GRep' (Rep1 f) -> a
forall (f :: * -> *) a. GIndex f => f a -> GRep' f -> a
gindex' (Rep1 f a -> GRep' (Rep1 f) -> a)
-> (f a -> Rep1 f a) -> f a -> GRep' (Rep1 f) -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> Rep1 f a
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' :: (GRep' (f :*: g) -> a) -> (:*:) f g a
gtabulate' GRep' (f :*: g) -> a
f = (GRep' f -> a) -> f a
forall (f :: * -> *) a. GTabulate f => (GRep' f -> a) -> f a
gtabulate' (Either (GRep' f) (GRep' g) -> a
GRep' (f :*: g) -> a
f (Either (GRep' f) (GRep' g) -> a)
-> (GRep' f -> Either (GRep' f) (GRep' g)) -> GRep' f -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GRep' f -> Either (GRep' f) (GRep' g)
forall a b. a -> Either a b
Left) f a -> g a -> (:*:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: (GRep' g -> a) -> g a
forall (f :: * -> *) a. GTabulate f => (GRep' f -> a) -> f a
gtabulate' (Either (GRep' f) (GRep' g) -> a
GRep' (f :*: g) -> a
f (Either (GRep' f) (GRep' g) -> a)
-> (GRep' g -> Either (GRep' f) (GRep' g)) -> GRep' g -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GRep' g -> Either (GRep' f) (GRep' g)
forall a b. b -> Either a b
Right)
instance (GIndex f, GIndex g) => GIndex (f :*: g) where
gindex' :: (:*:) f g a -> GRep' (f :*: g) -> a
gindex' (f a
a :*: g a
_) (Left i) = f a -> GRep' f -> a
forall (f :: * -> *) a. GIndex f => f a -> GRep' f -> a
gindex' f a
a GRep' f
i
gindex' (f a
_ :*: g a
b) (Right j) = g a -> GRep' g -> a
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' :: (GRep' (f :.: g) -> a) -> (:.:) f g a
gtabulate' GRep' (f :.: g) -> a
f = f (g a) -> (:.:) f g a
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Comp1 (f (g a) -> (:.:) f g a) -> f (g a) -> (:.:) f g a
forall a b. (a -> b) -> a -> b
$ (Rep f -> g a) -> f (g a)
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((Rep f -> g a) -> f (g a)) -> (Rep f -> g a) -> f (g a)
forall a b. (a -> b) -> a -> b
$ ((GRep' g -> a) -> g a) -> (Rep f -> GRep' g -> a) -> Rep f -> g a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (GRep' g -> a) -> g a
forall (f :: * -> *) a. GTabulate f => (GRep' f -> a) -> f a
gtabulate' ((Rep f -> GRep' g -> a) -> Rep f -> g a)
-> (Rep f -> GRep' g -> a) -> Rep f -> g a
forall a b. (a -> b) -> a -> b
$ (WrappedRep f -> GRep' g -> a)
-> (Rep f -> WrappedRep f) -> Rep f -> GRep' g -> a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((WrappedRep f, GRep' g) -> a) -> WrappedRep f -> GRep' g -> a
forall a b c. ((a, b) -> c) -> a -> b -> c
curry (WrappedRep f, GRep' g) -> a
GRep' (f :.: g) -> a
f) Rep f -> WrappedRep f
forall (f :: * -> *). Rep f -> WrappedRep f
WrapRep
instance (Representable f, GIndex g) => GIndex (f :.: g) where
gindex' :: (:.:) f g a -> GRep' (f :.: g) -> a
gindex' (Comp1 f (g a)
fg) (i, j) = g a -> GRep' g -> a
forall (f :: * -> *) a. GIndex f => f a -> GRep' f -> a
gindex' (f (g a) -> Rep f -> g a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f (g a)
fg (WrappedRep f -> Rep f
forall (f :: * -> *). WrappedRep f -> Rep f
unwrapRep WrappedRep f
i)) GRep' g
j
type instance GRep' Par1 = ()
instance GTabulate Par1 where
gtabulate' :: (GRep' Par1 -> a) -> Par1 a
gtabulate' GRep' Par1 -> a
f = a -> Par1 a
forall p. p -> Par1 p
Par1 (GRep' Par1 -> a
f ())
instance GIndex Par1 where
gindex' :: 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' :: (GRep' (Rec1 f) -> a) -> Rec1 f a
gtabulate' = ((Rep f -> a) -> f a) -> (WrappedRep f -> a) -> Rec1 f a
coerce ((Rep f -> a) -> f a
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' :: Rec1 f a -> GRep' (Rec1 f) -> a
gindex' = (f a -> Rep f -> a) -> Rec1 f a -> WrappedRep f -> a
coerce (f a -> Rep f -> a
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' :: (GRep' (M1 i c f) -> a) -> M1 i c f a
gtabulate' = f a -> M1 i c f a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (f a -> M1 i c f a)
-> ((GRep' f -> a) -> f a) -> (GRep' f -> a) -> M1 i c f a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. (GRep' f -> a) -> f a
forall (f :: * -> *) a. GTabulate f => (GRep' f -> a) -> f a
gtabulate'
instance GIndex f => GIndex (M1 i c f) where
gindex' :: M1 i c f a -> GRep' (M1 i c f) -> a
gindex' = f a -> GRep' f -> a
forall (f :: * -> *) a. GIndex f => f a -> GRep' f -> a
gindex' (f a -> GRep' f -> a)
-> (M1 i c f a -> f a) -> M1 i c f a -> GRep' f -> a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# M1 i c f a -> f a
forall i (c :: Meta) k (f :: k -> *) (p :: k). M1 i c f p -> f p
unM1
newtype WrappedRep f = WrapRep { 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 :: p (f a) (h (g b)) -> p (Rep f -> a) (h (Rep g -> b))
tabulated = ((Rep f -> a) -> f a)
-> (h (g b) -> h (Rep g -> b))
-> p (f a) (h (g b))
-> p (Rep f -> a) (h (Rep g -> b))
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap (Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((g b -> Rep g -> b) -> h (g b) -> h (Rep g -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap g b -> Rep g -> b
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index)
{-# INLINE tabulated #-}
fmapRep :: Representable f => (a -> b) -> f a -> f b
fmapRep :: (a -> b) -> f a -> f b
fmapRep a -> b
f = (Rep f -> b) -> f b
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((Rep f -> b) -> f b) -> (f a -> Rep f -> b) -> f a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> (Rep f -> a) -> Rep f -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f ((Rep f -> a) -> Rep f -> b)
-> (f a -> Rep f -> a) -> f a -> Rep f -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index
pureRep :: Representable f => a -> f a
pureRep :: a -> f a
pureRep = (Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((Rep f -> a) -> f a) -> (a -> Rep f -> a) -> a -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rep f -> a
forall a b. a -> b -> a
const
bindRep :: Representable f => f a -> (a -> f b) -> f b
bindRep :: f a -> (a -> f b) -> f b
bindRep f a
m a -> f b
f = (Rep f -> b) -> f b
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((Rep f -> b) -> f b) -> (Rep f -> b) -> f b
forall a b. (a -> b) -> a -> b
$ \Rep f
a -> f b -> Rep f -> b
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (a -> f b
f (f a -> Rep f -> a
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 :: (a -> f a) -> f a
mfixRep = (Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((Rep f -> a) -> f a)
-> ((a -> f a) -> Rep f -> a) -> (a -> f a) -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Rep f -> a) -> Rep f -> a
forall (m :: * -> *) a. MonadFix m => (a -> m a) -> m a
mfix ((a -> Rep f -> a) -> Rep f -> a)
-> ((a -> f a) -> a -> Rep f -> a) -> (a -> f a) -> Rep f -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (f a -> Rep f -> a) -> (a -> f a) -> a -> Rep f -> a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index
mzipWithRep :: Representable f => (a -> b -> c) -> f a -> f b -> f c
mzipWithRep :: (a -> b -> c) -> f a -> f b -> f c
mzipWithRep a -> b -> c
f f a
as f b
bs = (Rep f -> c) -> f c
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((Rep f -> c) -> f c) -> (Rep f -> c) -> f c
forall a b. (a -> b) -> a -> b
$ \Rep f
k -> a -> b -> c
f (f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
as Rep f
k) (f b -> Rep f -> b
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 :: f a -> f b -> f (a, b)
mzipRep f a
as f b
bs = (Rep f -> (a, b)) -> f (a, b)
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
as (Rep f -> a) -> (Rep f -> b) -> Rep f -> (a, b)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& f b -> Rep f -> b
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f b
bs)
askRep :: Representable f => f (Rep f)
askRep :: f (Rep f)
askRep = (Rep f -> Rep f) -> f (Rep f)
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate Rep f -> Rep f
forall a. a -> a
id
localRep :: Representable f => (Rep f -> Rep f) -> f a -> f a
localRep :: (Rep f -> Rep f) -> f a -> f a
localRep Rep f -> Rep f
f f a
m = (Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
m (Rep f -> a) -> (Rep f -> Rep f) -> Rep f -> a
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 :: f (a -> b) -> f a -> f b
apRep f (a -> b)
f f a
g = (Rep f -> b) -> f b
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (f (a -> b) -> Rep f -> a -> b
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f (a -> b)
f (Rep f -> a -> b) -> (Rep f -> a) -> Rep f -> b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f a -> Rep f -> a
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 :: w (f a) -> f (w a)
distributeRep w (f a)
wf = (Rep f -> w a) -> f (w a)
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (\Rep f
k -> (f a -> a) -> w (f a) -> w a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (f a -> Rep f -> a
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 :: (a -> f b) -> w a -> f (w b)
collectRep a -> f b
f w a
w = (Rep f -> w b) -> f (w b)
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (\Rep f
k -> (f b -> Rep f -> b
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
`index` Rep f
k) (f b -> b) -> (a -> f b) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> f b
f (a -> b) -> w a -> w b
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 :: (Rep f -> Rep f -> Rep f) -> f a -> f (f a)
duplicateRepBy Rep f -> Rep f -> Rep f
plus f a
w = (Rep f -> f a) -> f (f a)
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (\Rep f
m -> (Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
w (Rep f -> a) -> (Rep f -> Rep f) -> Rep f -> a
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 :: (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 = (Rep f -> b) -> f b
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (\Rep f
m -> f a -> b
f ((Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
w (Rep f -> a) -> (Rep f -> Rep f) -> Rep f -> a
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
= (f a -> Rep f -> a) -> Rep f -> f a -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index
duplicatedRep :: (Representable f, Semigroup (Rep f)) => f a -> f (f a)
duplicatedRep :: f a -> f (f a)
duplicatedRep = (Rep f -> Rep f -> Rep f) -> f a -> f (f a)
forall (f :: * -> *) a.
Representable f =>
(Rep f -> Rep f -> Rep f) -> f a -> f (f a)
duplicateRepBy Rep f -> Rep f -> Rep f
forall a. Semigroup a => a -> a -> a
(<>)
extendedRep :: (Representable f, Semigroup (Rep f)) => (f a -> b) -> f a -> f b
extendedRep :: (f a -> b) -> f a -> f b
extendedRep = (Rep f -> Rep f -> Rep f) -> (f a -> b) -> f a -> f b
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
forall a. Semigroup a => a -> a -> a
(<>)
duplicateRep :: (Representable f, Monoid (Rep f)) => f a -> f (f a)
duplicateRep :: f a -> f (f a)
duplicateRep = (Rep f -> Rep f -> Rep f) -> f a -> f (f a)
forall (f :: * -> *) a.
Representable f =>
(Rep f -> Rep f -> Rep f) -> f a -> f (f a)
duplicateRepBy Rep f -> Rep f -> Rep f
forall a. Monoid a => a -> a -> a
mappend
extendRep :: (Representable f, Monoid (Rep f)) => (f a -> b) -> f a -> f b
extendRep :: (f a -> b) -> f a -> f b
extendRep = (Rep f -> Rep f -> Rep f) -> (f a -> b) -> f a -> f b
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
forall a. Monoid a => a -> a -> a
mappend
extractRep :: (Representable f, Monoid (Rep f)) => f a -> a
= Rep f -> f a -> a
forall (f :: * -> *) a. Representable f => Rep f -> f a -> a
extractRepBy Rep f
forall a. Monoid a => a
mempty
imapRep :: Representable r => (Rep r -> a -> a') -> (r a -> r a')
imapRep :: (Rep r -> a -> a') -> r a -> r a'
imapRep Rep r -> a -> a'
f r a
xs = (Rep r -> a') -> r a'
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Rep r -> a -> a'
f (Rep r -> a -> a') -> (Rep r -> a) -> Rep r -> a'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> r a -> Rep r -> a
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 :: (Rep r -> a -> m) -> r a -> m
ifoldMapRep Rep r -> a -> m
ix r a
xs = r m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ((Rep r -> m) -> r m
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (\(i :: Rep r) -> Rep r -> a -> m
ix Rep r
i (a -> m) -> a -> m
forall a b. (a -> b) -> a -> b
$ r a -> Rep r -> a
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 :: (Rep r -> a -> f a') -> r a -> f (r a')
itraverseRep Rep r -> a -> f a'
ix r a
xs = r (f a') -> f (r a')
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (r (f a') -> f (r a')) -> r (f a') -> f (r a')
forall a b. (a -> b) -> a -> b
$ (Rep r -> f a') -> r (f a')
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Rep r -> a -> f a'
ix (Rep r -> a -> f a') -> (Rep r -> a) -> Rep r -> f a'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> r a -> Rep r -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index r a
xs)
instance Representable Proxy where
type Rep Proxy = Void
index :: Proxy a -> Rep Proxy -> a
index Proxy a
Proxy = Rep Proxy -> a
forall a. Void -> a
absurd
tabulate :: (Rep Proxy -> a) -> Proxy a
tabulate Rep Proxy -> a
_ = Proxy a
forall k (t :: k). Proxy t
Proxy
instance Representable Identity where
type Rep Identity = ()
index :: Identity a -> Rep Identity -> a
index (Identity a
a) () = a
a
tabulate :: (Rep Identity -> a) -> Identity a
tabulate Rep Identity -> a
f = a -> Identity a
forall a. a -> Identity a
Identity (Rep Identity -> a
f ())
instance Representable (Tagged t) where
type Rep (Tagged t) = ()
index :: Tagged t a -> Rep (Tagged t) -> a
index (Tagged a
a) () = a
a
tabulate :: (Rep (Tagged t) -> a) -> Tagged t a
tabulate Rep (Tagged t) -> a
f = a -> Tagged t a
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 :: IdentityT m a -> Rep (IdentityT m) -> a
index = m a -> Rep m -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (m a -> Rep m -> a)
-> (IdentityT m a -> m a) -> IdentityT m a -> Rep m -> a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# IdentityT m a -> m a
forall k (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT
tabulate :: (Rep (IdentityT m) -> a) -> IdentityT m a
tabulate = m a -> IdentityT m a
forall k (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m a -> IdentityT m a)
-> ((Rep m -> a) -> m a) -> (Rep m -> a) -> IdentityT m a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. (Rep m -> a) -> m a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate
instance Representable ((->) e) where
type Rep ((->) e) = e
index :: (e -> a) -> Rep ((->) e) -> a
index = (e -> a) -> Rep ((->) e) -> a
forall a. a -> a
id
tabulate :: (Rep ((->) e) -> a) -> e -> a
tabulate = (Rep ((->) e) -> a) -> e -> a
forall a. a -> a
id
instance Representable m => Representable (ReaderT e m) where
type Rep (ReaderT e m) = (e, Rep m)
index :: ReaderT e m a -> Rep (ReaderT e m) -> a
index (ReaderT e -> m a
f) (e,k) = m a -> Rep m -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (e -> m a
f e
e) Rep m
k
tabulate :: (Rep (ReaderT e m) -> a) -> ReaderT e m a
tabulate = (e -> m a) -> ReaderT e m a
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((e -> m a) -> ReaderT e m a)
-> (((e, Rep m) -> a) -> e -> m a)
-> ((e, Rep m) -> a)
-> ReaderT e m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Rep m -> a) -> m a) -> (e -> Rep m -> a) -> e -> m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Rep m -> a) -> m a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((e -> Rep m -> a) -> e -> m a)
-> (((e, Rep m) -> a) -> e -> Rep m -> a)
-> ((e, Rep m) -> a)
-> e
-> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((e, Rep m) -> a) -> e -> Rep m -> a
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 :: Compose f g a -> Rep (Compose f g) -> a
index (Compose f (g a)
fg) (i,j) = g a -> Rep g -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (f (g a) -> Rep f -> g a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f (g a)
fg Rep f
i) Rep g
j
tabulate :: (Rep (Compose f g) -> a) -> Compose f g a
tabulate = f (g a) -> Compose f g a
forall k k1 (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (g a) -> Compose f g a)
-> (((Rep f, Rep g) -> a) -> f (g a))
-> ((Rep f, Rep g) -> a)
-> Compose f g a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rep f -> g a) -> f (g a)
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((Rep f -> g a) -> f (g a))
-> (((Rep f, Rep g) -> a) -> Rep f -> g a)
-> ((Rep f, Rep g) -> a)
-> f (g a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Rep g -> a) -> g a) -> (Rep f -> Rep g -> a) -> Rep f -> g a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Rep g -> a) -> g a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((Rep f -> Rep g -> a) -> Rep f -> g a)
-> (((Rep f, Rep g) -> a) -> Rep f -> Rep g -> a)
-> ((Rep f, Rep g) -> a)
-> Rep f
-> g a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Rep f, Rep g) -> a) -> Rep f -> Rep g -> a
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 :: TracedT s w a -> Rep (TracedT s w) -> a
index (TracedT w (s -> a)
w) (e,k) = w (s -> a) -> Rep w -> s -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index w (s -> a)
w Rep w
k s
e
tabulate :: (Rep (TracedT s w) -> a) -> TracedT s w a
tabulate = w (s -> a) -> TracedT s w a
forall m (w :: * -> *) a. w (m -> a) -> TracedT m w a
TracedT (w (s -> a) -> TracedT s w a)
-> (((s, Rep w) -> a) -> w (s -> a))
-> ((s, Rep w) -> a)
-> TracedT s w a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Co w (s -> a) -> w (s -> a)
forall (f :: * -> *) a. Co f a -> f a
unCo (Co w (s -> a) -> w (s -> a))
-> (((s, Rep w) -> a) -> Co w (s -> a))
-> ((s, Rep w) -> a)
-> w (s -> a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Rep w -> a) -> Co w a) -> (s -> Rep w -> a) -> Co w (s -> a)
forall (g :: * -> *) (f :: * -> *) a b.
(Distributive g, Functor f) =>
(a -> g b) -> f a -> g (f b)
collect (w a -> Co w a
forall (f :: * -> *) a. f a -> Co f a
Co (w a -> Co w a) -> ((Rep w -> a) -> w a) -> (Rep w -> a) -> Co w a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. (Rep w -> a) -> w a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate) ((s -> Rep w -> a) -> Co w (s -> a))
-> (((s, Rep w) -> a) -> s -> Rep w -> a)
-> ((s, Rep w) -> a)
-> Co w (s -> a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((s, Rep w) -> a) -> s -> Rep w -> a
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 :: Product f g a -> Rep (Product f g) -> a
index (Pair f a
a g a
_) (Left i) = f a -> Rep f -> a
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 j) = g a -> Rep g -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index g a
b Rep g
j
tabulate :: (Rep (Product f g) -> a) -> Product f g a
tabulate Rep (Product f g) -> a
f = f a -> g a -> Product f g a
forall k (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair ((Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Either (Rep f) (Rep g) -> a
Rep (Product f g) -> a
f (Either (Rep f) (Rep g) -> a)
-> (Rep f -> Either (Rep f) (Rep g)) -> Rep f -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rep f -> Either (Rep f) (Rep g)
forall a b. a -> Either a b
Left)) ((Rep g -> a) -> g a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Either (Rep f) (Rep g) -> a
Rep (Product f g) -> a
f (Either (Rep f) (Rep g) -> a)
-> (Rep g -> Either (Rep f) (Rep g)) -> Rep g -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rep g -> Either (Rep f) (Rep g)
forall a b. b -> Either a b
Right))
instance Representable f => Representable (Cofree f) where
type Rep (Cofree f) = Seq (Rep f)
index :: Cofree f a -> Rep (Cofree f) -> a
index (a
a :< f (Cofree f a)
as) Rep (Cofree f)
key = case Seq (Rep f) -> ViewL (Rep f)
forall a. Seq a -> ViewL a
Seq.viewl Seq (Rep f)
Rep (Cofree f)
key of
ViewL (Rep f)
Seq.EmptyL -> a
a
Rep f
k Seq.:< Seq (Rep f)
ks -> Cofree f a -> Rep (Cofree f) -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (f (Cofree f a) -> Rep f -> Cofree f a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f (Cofree f a)
as Rep f
k) Seq (Rep f)
Rep (Cofree f)
ks
tabulate :: (Rep (Cofree f) -> a) -> Cofree f a
tabulate Rep (Cofree f) -> a
f = Rep (Cofree f) -> a
f Rep (Cofree f)
forall a. Seq a
Seq.empty a -> f (Cofree f a) -> Cofree f a
forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< (Rep f -> Cofree f a) -> f (Cofree f a)
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (\Rep f
k -> (Rep (Cofree f) -> a) -> Cofree f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Seq (Rep f) -> a
Rep (Cofree f) -> a
f (Seq (Rep f) -> a)
-> (Seq (Rep f) -> Seq (Rep f)) -> Seq (Rep f) -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rep f
k Rep f -> Seq (Rep f) -> Seq (Rep f)
forall a. a -> Seq a -> Seq a
Seq.<|)))
instance Representable f => Representable (Backwards f) where
type Rep (Backwards f) = Rep f
index :: Backwards f a -> Rep (Backwards f) -> a
index = f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (f a -> Rep f -> a)
-> (Backwards f a -> f a) -> Backwards f a -> Rep f -> a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# Backwards f a -> f a
forall k (f :: k -> *) (a :: k). Backwards f a -> f a
forwards
tabulate :: (Rep (Backwards f) -> a) -> Backwards f a
tabulate = f a -> Backwards f a
forall k (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards (f a -> Backwards f a)
-> ((Rep f -> a) -> f a) -> (Rep f -> a) -> Backwards f a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. (Rep f -> a) -> f a
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 :: Reverse f a -> Rep (Reverse f) -> a
index = f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (f a -> Rep f -> a)
-> (Reverse f a -> f a) -> Reverse f a -> Rep f -> a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# Reverse f a -> f a
forall k (f :: k -> *) (a :: k). Reverse f a -> f a
getReverse
tabulate :: (Rep (Reverse f) -> a) -> Reverse f a
tabulate = f a -> Reverse f a
forall k (f :: k -> *) (a :: k). f a -> Reverse f a
Reverse (f a -> Reverse f a)
-> ((Rep f -> a) -> f a) -> (Rep f -> a) -> Reverse f a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. (Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate
instance Representable Monoid.Dual where
type Rep Monoid.Dual = ()
index :: Dual a -> Rep Dual -> a
index (Monoid.Dual a
d) () = a
d
tabulate :: (Rep Dual -> a) -> Dual a
tabulate Rep Dual -> a
f = a -> Dual a
forall a. a -> Dual a
Monoid.Dual (Rep Dual -> a
f ())
instance Representable Monoid.Product where
type Rep Monoid.Product = ()
index :: Product a -> Rep Product -> a
index (Monoid.Product a
p) () = a
p
tabulate :: (Rep Product -> a) -> Product a
tabulate Rep Product -> a
f = a -> Product a
forall a. a -> Product a
Monoid.Product (Rep Product -> a
f ())
instance Representable Monoid.Sum where
type Rep Monoid.Sum = ()
index :: Sum a -> Rep Sum -> a
index (Monoid.Sum a
s) () = a
s
tabulate :: (Rep Sum -> a) -> Sum a
tabulate Rep Sum -> a
f = a -> Sum a
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 :: Complex a -> Rep Complex -> a
index (a
r :+ a
i) Rep Complex
key = if Bool
Rep Complex
key then a
i else a
r
tabulate :: (Rep Complex -> a) -> Complex a
tabulate Rep Complex -> a
f = Rep Complex -> a
f Bool
Rep Complex
False a -> a -> Complex a
forall a. a -> a -> Complex a
:+ Rep Complex -> a
f Bool
Rep Complex
True
#endif
instance Representable U1 where
type Rep U1 = Void
index :: U1 a -> Rep U1 -> a
index U1 a
U1 = Rep U1 -> a
forall a. Void -> a
absurd
tabulate :: (Rep U1 -> a) -> U1 a
tabulate Rep U1 -> a
_ = 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 :: (:*:) f g a -> Rep (f :*: g) -> a
index (f a
a :*: g a
_) (Left i) = f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
a Rep f
i
index (f a
_ :*: g a
b) (Right j) = g a -> Rep g -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index g a
b Rep g
j
tabulate :: (Rep (f :*: g) -> a) -> (:*:) f g a
tabulate Rep (f :*: g) -> a
f = (Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Either (Rep f) (Rep g) -> a
Rep (f :*: g) -> a
f (Either (Rep f) (Rep g) -> a)
-> (Rep f -> Either (Rep f) (Rep g)) -> Rep f -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rep f -> Either (Rep f) (Rep g)
forall a b. a -> Either a b
Left) f a -> g a -> (:*:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: (Rep g -> a) -> g a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (Either (Rep f) (Rep g) -> a
Rep (f :*: g) -> a
f (Either (Rep f) (Rep g) -> a)
-> (Rep g -> Either (Rep f) (Rep g)) -> Rep g -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rep g -> Either (Rep f) (Rep g)
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 :: (:.:) f g a -> Rep (f :.: g) -> a
index (Comp1 f (g a)
fg) (i, j) = g a -> Rep g -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (f (g a) -> Rep f -> g a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f (g a)
fg Rep f
i) Rep g
j
tabulate :: (Rep (f :.: g) -> a) -> (:.:) f g a
tabulate = f (g a) -> (:.:) f g a
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Comp1 (f (g a) -> (:.:) f g a)
-> (((Rep f, Rep g) -> a) -> f (g a))
-> ((Rep f, Rep g) -> a)
-> (:.:) f g a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rep f -> g a) -> f (g a)
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((Rep f -> g a) -> f (g a))
-> (((Rep f, Rep g) -> a) -> Rep f -> g a)
-> ((Rep f, Rep g) -> a)
-> f (g a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Rep g -> a) -> g a) -> (Rep f -> Rep g -> a) -> Rep f -> g a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Rep g -> a) -> g a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((Rep f -> Rep g -> a) -> Rep f -> g a)
-> (((Rep f, Rep g) -> a) -> Rep f -> Rep g -> a)
-> ((Rep f, Rep g) -> a)
-> Rep f
-> g a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Rep f, Rep g) -> a) -> Rep f -> Rep g -> a
forall a b c. ((a, b) -> c) -> a -> b -> c
curry
instance Representable Par1 where
type Rep Par1 = ()
index :: Par1 a -> Rep Par1 -> a
index (Par1 a
a) () = a
a
tabulate :: (Rep Par1 -> a) -> Par1 a
tabulate Rep Par1 -> a
f = a -> Par1 a
forall p. p -> Par1 p
Par1 (Rep Par1 -> a
f ())
instance Representable f => Representable (Rec1 f) where
type Rep (Rec1 f) = Rep f
index :: Rec1 f a -> Rep (Rec1 f) -> a
index = f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (f a -> Rep f -> a) -> (Rec1 f a -> f a) -> Rec1 f a -> Rep f -> a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# Rec1 f a -> f a
forall k (f :: k -> *) (p :: k). Rec1 f p -> f p
unRec1
tabulate :: (Rep (Rec1 f) -> a) -> Rec1 f a
tabulate = f a -> Rec1 f a
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Rec1 (f a -> Rec1 f a)
-> ((Rep f -> a) -> f a) -> (Rep f -> a) -> Rec1 f a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. (Rep f -> a) -> f a
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 :: M1 i c f a -> Rep (M1 i c f) -> a
index = f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (f a -> Rep f -> a)
-> (M1 i c f a -> f a) -> M1 i c f a -> Rep f -> a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# M1 i c f a -> f a
forall i (c :: Meta) k (f :: k -> *) (p :: k). M1 i c f p -> f p
unM1
tabulate :: (Rep (M1 i c f) -> a) -> M1 i c f a
tabulate = f a -> M1 i c f a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (f a -> M1 i c f a)
-> ((Rep f -> a) -> f a) -> (Rep f -> a) -> M1 i c f a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. (Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate
newtype Co f a = Co { Co f a -> f a
unCo :: f a } deriving a -> Co f b -> Co f a
(a -> b) -> Co f a -> Co f b
(forall a b. (a -> b) -> Co f a -> Co f b)
-> (forall a b. a -> Co f b -> Co f a) -> Functor (Co f)
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
<$ :: a -> Co f b -> Co f a
$c<$ :: forall (f :: * -> *) a b. Functor f => a -> Co f b -> Co f a
fmap :: (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 :: (Rep (Co f) -> a) -> Co f a
tabulate = f a -> Co f a
forall (f :: * -> *) a. f a -> Co f a
Co (f a -> Co f a) -> ((Rep f -> a) -> f a) -> (Rep f -> a) -> Co f a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. (Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate
index :: Co f a -> Rep (Co f) -> a
index = f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index (f a -> Rep f -> a) -> (Co f a -> f a) -> Co f a -> Rep f -> a
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible b a) =>
p b c -> q a b -> p a c
.# Co f a -> f a
forall (f :: * -> *) a. Co f a -> f a
unCo
instance Representable f => Apply (Co f) where
<.> :: Co f (a -> b) -> Co f a -> Co f 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 :: a -> Co f a
pure = a -> Co f a
forall (f :: * -> *) a. Representable f => a -> f a
pureRep
<*> :: Co f (a -> b) -> Co f a -> Co f 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 :: f (Co f a) -> Co f (f a)
distribute = f (Co f a) -> Co f (f a)
forall (f :: * -> *) (w :: * -> *) a.
(Representable f, Functor w) =>
w (f a) -> f (w a)
distributeRep
collect :: (a -> Co f b) -> f a -> Co f (f b)
collect = (a -> Co f b) -> f a -> Co f (f b)
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
>>- :: Co f a -> (a -> Co f b) -> Co f 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 :: a -> Co f a
return = a -> Co f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
>>= :: Co f a -> (a -> Co f b) -> Co f 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 = Co f a
forall (f :: * -> *). Representable f => f (Rep f)
askRep
local :: (a -> a) -> Co f a -> Co f a
local = (a -> a) -> Co f a -> Co f a
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 :: (Co f a -> b) -> Co f a -> Co f b
extended = (Co f a -> b) -> Co f a -> Co f b
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 :: (Co f a -> b) -> Co f a -> Co f b
extend = (Co f a -> b) -> Co f a -> Co f b
forall (f :: * -> *) a b.
(Representable f, Monoid (Rep f)) =>
(f a -> b) -> f a -> f b
extendRep
extract :: Co f a -> a
extract = Co f a -> a
forall (f :: * -> *) a.
(Representable f, Monoid (Rep f)) =>
f a -> a
extractRep
instance ComonadTrans Co where
lower :: 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 :: (a -> b -> c) -> f a -> f b -> f c
liftR2 a -> b -> c
f f a
fa f b
fb = (Rep f -> c) -> f c
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((Rep f -> c) -> f c) -> (Rep f -> c) -> f c
forall a b. (a -> b) -> a -> b
$ \Rep f
i -> a -> b -> c
f (f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
fa Rep f
i) (f b -> Rep f -> b
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 :: (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 = (Rep f -> d) -> f d
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((Rep f -> d) -> f d) -> (Rep f -> d) -> f d
forall a b. (a -> b) -> a -> b
$ \Rep f
i -> a -> b -> c -> d
f (f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
fa Rep f
i) (f b -> Rep f -> b
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f b
fb Rep f
i) (f c -> Rep f -> c
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f c
fc Rep f
i)