naperian-0.1.0.0: Efficient representable functors

Safe HaskellNone
LanguageHaskell2010

Data.Naperian

Contents

Synopsis

Documentation

class Distributive f => Naperian f where Source #

A more powerful form of Distributive functor, which is equal in power to a Representable functor (for some Rep), but which can be implemented asymptotically more efficiently for instances which don't support random access.

A functor is Naperian/Representable iff it's isomorphic to (->) r for some r. Such a functor can be thought of as a container of a fixed size, where r is the type of positions in the container. By representing a position as a function of type forall x. f x -> x, which gets the value at that position, a Naperian/Representable functor can equivalently be shown to be one for which f is isomorphic to (->) (forall x. f x -> x)

These isomorphisms are equivalent to distribute1 + fmap, but the latter can be implemented more efficiently for containers which don't support random access.

Minimal complete definition

distribute1

Methods

distribute1 :: Functor1 w => w f -> f (w Identity) Source #

distribute1 :: (Generic1 f, Naperian (Rep1 f), Functor1 w) => w f -> f (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w f -> f a Source #

collect1 :: Functor1 w => (forall x. g x -> f x) -> w g -> f (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> f x) -> w g -> f a Source #

ntabulate :: ((forall x. f x -> x) -> a) -> f a Source #

Instances

Naperian U1 Source #

since distributive-0.5.1

Methods

distribute1 :: Functor1 w => w U1 -> U1 (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w U1 -> U1 a Source #

collect1 :: Functor1 w => (forall x. g x -> U1 x) -> w g -> U1 (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> U1 x) -> w g -> U1 a Source #

ntabulate :: ((forall x. U1 x -> x) -> a) -> U1 a Source #

Naperian Par1 Source #

since distributive-0.5.1

Methods

distribute1 :: Functor1 w => w Par1 -> Par1 (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w Par1 -> Par1 a Source #

collect1 :: Functor1 w => (forall x. g x -> Par1 x) -> w g -> Par1 (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> Par1 x) -> w g -> Par1 a Source #

ntabulate :: ((forall x. Par1 x -> x) -> a) -> Par1 a Source #

Naperian Identity Source # 

Methods

distribute1 :: Functor1 w => w Identity -> Identity (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w Identity -> Identity a Source #

collect1 :: Functor1 w => (forall x. g x -> Identity x) -> w g -> Identity (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> Identity x) -> w g -> Identity a Source #

ntabulate :: ((forall x. Identity x -> x) -> a) -> Identity a Source #

Naperian Stream Source # 

Methods

distribute1 :: Functor1 w => w Stream -> Stream (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w Stream -> Stream a Source #

collect1 :: Functor1 w => (forall x. g x -> Stream x) -> w g -> Stream (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> Stream x) -> w g -> Stream a Source #

ntabulate :: ((forall x. Stream x -> x) -> a) -> Stream a Source #

Naperian ((->) e) Source # 

Methods

distribute1 :: Functor1 w => w ((->) e) -> e -> w Identity Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w ((->) e) -> e -> a Source #

collect1 :: Functor1 w => (forall x. g x -> e -> x) -> w g -> e -> w Identity Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> e -> x) -> w g -> e -> a Source #

ntabulate :: ((forall x. (e -> x) -> x) -> a) -> e -> a Source #

Naperian f => Naperian (Rec1 f) Source #

since distributive-0.5.1

Methods

distribute1 :: Functor1 w => w (Rec1 f) -> Rec1 f (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w (Rec1 f) -> Rec1 f a Source #

collect1 :: Functor1 w => (forall x. g x -> Rec1 f x) -> w g -> Rec1 f (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> Rec1 f x) -> w g -> Rec1 f a Source #

ntabulate :: ((forall x. Rec1 f x -> x) -> a) -> Rec1 f a Source #

Naperian f => Naperian (Cofree f) Source # 

Methods

distribute1 :: Functor1 w => w (Cofree f) -> Cofree f (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w (Cofree f) -> Cofree f a Source #

collect1 :: Functor1 w => (forall x. g x -> Cofree f x) -> w g -> Cofree f (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> Cofree f x) -> w g -> Cofree f a Source #

ntabulate :: ((forall x. Cofree f x -> x) -> a) -> Cofree f a Source #

(Naperian f, Naperian g) => Naperian ((:*:) f g) Source #

since distributive-0.5.1

Methods

distribute1 :: Functor1 w => w (f :*: g) -> (f :*: g) (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w (f :*: g) -> (f :*: g) a Source #

collect1 :: Functor1 w => (forall x. g x -> (f :*: g) x) -> w g -> (f :*: g) (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> (f :*: g) x) -> w g -> (f :*: g) a Source #

ntabulate :: ((forall x. (f :*: g) x -> x) -> a) -> (f :*: g) a Source #

(Naperian f, Naperian g) => Naperian ((:.:) f g) Source #

since distributive-0.5.1

Methods

distribute1 :: Functor1 w => w (f :.: g) -> (f :.: g) (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w (f :.: g) -> (f :.: g) a Source #

collect1 :: Functor1 w => (forall x. g x -> (f :.: g) x) -> w g -> (f :.: g) (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> (f :.: g) x) -> w g -> (f :.: g) a Source #

ntabulate :: ((forall x. (f :.: g) x -> x) -> a) -> (f :.: g) a Source #

Naperian w => Naperian (TracedT s w) Source # 

Methods

distribute1 :: Functor1 w => w (TracedT s w) -> TracedT s w (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w (TracedT s w) -> TracedT s w a Source #

collect1 :: Functor1 w => (forall x. g x -> TracedT s w x) -> w g -> TracedT s w (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> TracedT s w x) -> w g -> TracedT s w a Source #

ntabulate :: ((forall x. TracedT s w x -> x) -> a) -> TracedT s w a Source #

Naperian f => Naperian (IdentityT * f) Source # 

Methods

distribute1 :: Functor1 w => w (IdentityT * f) -> IdentityT * f (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w (IdentityT * f) -> IdentityT * f a Source #

collect1 :: Functor1 w => (forall x. g x -> IdentityT * f x) -> w g -> IdentityT * f (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> IdentityT * f x) -> w g -> IdentityT * f a Source #

ntabulate :: ((forall x. IdentityT * f x -> x) -> a) -> IdentityT * f a Source #

Naperian f => Naperian (M1 i c f) Source #

since distributive-0.5.1

Methods

distribute1 :: Functor1 w => w (M1 i c f) -> M1 i c f (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w (M1 i c f) -> M1 i c f a Source #

collect1 :: Functor1 w => (forall x. g x -> M1 i c f x) -> w g -> M1 i c f (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> M1 i c f x) -> w g -> M1 i c f a Source #

ntabulate :: ((forall x. M1 i c f x -> x) -> a) -> M1 i c f a Source #

(Naperian f, Naperian g) => Naperian (Product * f g) Source # 

Methods

distribute1 :: Functor1 w => w (Product * f g) -> Product * f g (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w (Product * f g) -> Product * f g a Source #

collect1 :: Functor1 w => (forall x. g x -> Product * f g x) -> w g -> Product * f g (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> Product * f g x) -> w g -> Product * f g a Source #

ntabulate :: ((forall x. Product * f g x -> x) -> a) -> Product * f g a Source #

Naperian f => Naperian (ReaderT * e f) Source # 

Methods

distribute1 :: Functor1 w => w (ReaderT * e f) -> ReaderT * e f (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w (ReaderT * e f) -> ReaderT * e f a Source #

collect1 :: Functor1 w => (forall x. g x -> ReaderT * e f x) -> w g -> ReaderT * e f (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> ReaderT * e f x) -> w g -> ReaderT * e f a Source #

ntabulate :: ((forall x. ReaderT * e f x -> x) -> a) -> ReaderT * e f a Source #

(Naperian f, Naperian g) => Naperian (Compose * * f g) Source # 

Methods

distribute1 :: Functor1 w => w (Compose * * f g) -> Compose * * f g (w Identity) Source #

cotraverse1 :: Functor1 w => (w Identity -> a) -> w (Compose * * f g) -> Compose * * f g a Source #

collect1 :: Functor1 w => (forall x. g x -> Compose * * f g x) -> w g -> Compose * * f g (w Identity) Source #

twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> Compose * * f g x) -> w g -> Compose * * f g a Source #

ntabulate :: ((forall x. Compose * * f g x -> x) -> a) -> Compose * * f g a Source #

nindex :: f a -> (forall x. f x -> x) -> a Source #

Inverse of ntabulate

Default Definitions

Naperian

type Distribute1 f = forall w. Functor1 w => w f -> f (w Identity) Source #

Alias for the type of distribute1

distributeTabulate :: Naperian f => Distribute1 f Source #

Derive distribute1 given an implementation of ntabulate

distributeIso :: Naperian g => (forall x. f x -> g x) -> (forall x. g x -> f x) -> Distribute1 f Source #

Derive distribute1 via an isomorphism

distributeCoerce :: forall g f. Naperian g => (forall x. Coercion (g x) (f x)) -> Distribute1 f Source #

Derive distribute1 via a coercion

Functor

fmapCotraverse1 :: Naperian f => (a -> b) -> f a -> f b Source #

Derive fmap given an implementation of cotraverse1. Note that an implementation of distribute1 is not sufficient!

Apply/Applicative/MonadZip

zipWithNap :: Naperian f => (a -> b -> c) -> f a -> f b -> f c Source #

apNap :: Naperian f => f (a -> b) -> f a -> f b Source #

pureNap :: Naperian f => a -> f a Source #

Bind/Monad

bindNap :: Naperian f => f a -> (a -> f b) -> f b Source #

Distributive

distributeNap :: (Naperian f, Functor w) => w (f a) -> f (w a) Source #

collectNap :: (Naperian f, Functor w) => (a -> f b) -> w a -> f (w b) Source #

Representable

newtype Logarithm f Source #

Constructors

Logarithm 

Fields

tabulateLog :: Naperian f => (Logarithm f -> a) -> f a Source #

indexLog :: f a -> Logarithm f -> a Source #