Safe Haskell | None |
---|---|
Language | Haskell2010 |
- module Data.Functor1
- class Distributive f => Naperian f where
- nindex :: f a -> (forall x. f x -> x) -> a
- type Distribute1 f = forall w. Functor1 w => w f -> f (w Identity)
- distributeTabulate :: Naperian f => Distribute1 f
- distributeRepresentable :: Representable f => Distribute1 f
- distributeIso :: Naperian g => (forall x. f x -> g x) -> (forall x. g x -> f x) -> Distribute1 f
- distributeCoerce :: forall g f. Naperian g => (forall x. Coercion (g x) (f x)) -> Distribute1 f
- fmapCotraverse1 :: Naperian f => (a -> b) -> f a -> f b
- zipWithNap :: Naperian f => (a -> b -> c) -> f a -> f b -> f c
- apNap :: Naperian f => f (a -> b) -> f a -> f b
- pureNap :: Naperian f => a -> f a
- bindNap :: Naperian f => f a -> (a -> f b) -> f b
- distributeNap :: (Naperian f, Functor w) => w (f a) -> f (w a)
- collectNap :: (Naperian f, Functor w) => (a -> f b) -> w a -> f (w b)
- newtype Logarithm f = Logarithm {
- runLogarithm :: forall x. f x -> x
- tabulateLog :: Naperian f => (Logarithm f -> a) -> f a
- indexLog :: f a -> Logarithm f -> a
Documentation
module Data.Functor1
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.
distribute1 :: Functor1 w => w f -> f (w Identity) Source #
distribute1
.Applied
=fmap
(Applied
.Identity
)distribute1
(Const
x) =Const
x<$
xs
distribute1 :: (Generic1 f, Naperian (Rep1 f), Functor1 w) => w f -> f (w Identity) Source #
distribute1
.Applied
=fmap
(Applied
.Identity
)distribute1
(Const
x) =Const
x<$
xs
cotraverse1 :: Functor1 w => (w Identity -> a) -> w f -> f a Source #
cotraverse1
f =fmap
f .distribute1
collect1 :: Functor1 w => (forall x. g x -> f x) -> w g -> f (w Identity) Source #
collect1
f =distribute1
.map1
f
twiddle1 :: Functor1 w => (w Identity -> a) -> (forall x. g x -> f x) -> w g -> f a Source #
twiddle1
f g =fmap
f .distribute1
.map1
g
Naperian U1 Source # | since distributive-0.5.1 |
Naperian Par1 Source # | since distributive-0.5.1 |
Naperian Identity Source # | |
Naperian Stream Source # | |
Naperian ((->) e) Source # | |
Naperian f => Naperian (Rec1 f) Source # | since distributive-0.5.1 |
Naperian f => Naperian (Cofree f) Source # | |
(Naperian f, Naperian g) => Naperian ((:*:) f g) Source # | since distributive-0.5.1 |
(Naperian f, Naperian g) => Naperian ((:.:) f g) Source # | since distributive-0.5.1 |
Naperian w => Naperian (TracedT s w) Source # | |
Naperian f => Naperian (IdentityT * f) Source # | |
Naperian f => Naperian (M1 i c f) Source # | since distributive-0.5.1 |
(Naperian f, Naperian g) => Naperian (Product * f g) Source # | |
Naperian f => Naperian (ReaderT * e f) Source # | |
(Naperian f, Naperian g) => Naperian (Compose * * f g) Source # | |
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
distributeRepresentable :: Representable f => Distribute1 f Source #
Derive distribute1
given an instance of Representable
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 #
Bind/Monad
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
Logarithm | |
|
tabulateLog :: Naperian f => (Logarithm f -> a) -> f a Source #