fraxl-0.1.0.0: Cached and parallel data fetching.

Safe HaskellSafe
LanguageHaskell2010

Control.Applicative.Fraxl.Free

Description

A faster free applicative. Based on Dave Menendez's work.

Synopsis

Documentation

data ASeq f a where Source

Constructors

ANil :: ASeq f () 
ACons :: f a -> ASeq f u -> ASeq f (a, u) 

reduceASeq :: Applicative f => ASeq f u -> f u Source

reduceASeq a sequence of applicative effects into an applicative.

newtype Ap f a Source

The faster free Applicative.

Constructors

Ap 

Fields

unAp :: forall u y z. (forall x. (x -> y) -> ASeq f x -> z) -> (u -> a -> y) -> ASeq f u -> z
 

Instances

Monad m => MonadFraxl f (FreerT f m) Source 
(Monad m, (∈) (* -> *) f r) => MonadFraxl f (Fraxl r m) Source 
Functor (Ap f) Source 
Applicative (Ap f) Source 

liftAp :: f a -> Ap f a Source

A version of lift that can be used with just a Functor for f.

retractAp :: Applicative f => Ap f a -> f a Source

Interprets the free applicative functor over f using the semantics for pure and <*> given by the Applicative instance for f.

retractApp == runAp id

runAp :: Applicative g => (forall x. f x -> g x) -> Ap f a -> g a Source

Given a natural transformation from f to g, this gives a canonical monoidal natural transformation from Ap f to g.

runAp t == retractApp . hoistApp t

runAp_ :: Monoid m => (forall a. f a -> m) -> Ap f b -> m Source

Perform a monoidal analysis over free applicative value.

Example:

count :: Ap f a -> Int
count = getSum . runAp_ (\_ -> Sum 1)

hoistASeq :: (forall x. f x -> g x) -> ASeq f a -> ASeq g a Source

Transform a sequence of f into a sequence of g.

traverseASeq :: Applicative h => (forall x. f x -> h (g x)) -> ASeq f a -> h (ASeq g a) Source

Traverse a sequence with resepect to its interpretation type f.

rebaseASeq :: ASeq f u -> (forall x. (x -> y) -> ASeq f x -> z) -> (v -> u -> y) -> ASeq f v -> z Source

It may not look like it, but this appends two sequences. See Dave Menendez's work for more explanation.

hoistAp :: (forall x. f x -> g x) -> Ap f a -> Ap g a Source

Given a natural transformation from f to g this gives a monoidal natural transformation from Ap f to Ap g.