fraxl-0.1.0.0: Cached and parallel data fetching.

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trans.Fraxl

Contents

Synopsis

The Fraxl Monad

type FreerT f = FreeT (Ap f) Source

Fraxl is based on a particular Freer monad. This Freer monad has applicative optimization, which is used to parallelize effects.

type Fraxl r = FreerT (Union r) Source

Fraxl is just the FreerT monad transformer, applied with Union. This is because Fraxl is just a free monad over a variety of data sources.

type Fetch f m a = ASeq f a -> m (ASeq m a) Source

A data source is an effect f that operates in some monad m. Given a sequence of effects, a data source should use m to prepare a corresponding sequence of results.

runFraxl :: Monad m => (forall a'. Fetch f m a') -> FreerT f m a -> m a Source

Runs a Fraxl computation, using a given Fetch function for f. This takes FreerT as a parameter rather than Fraxl, because Fraxl is meant for a union of effects, but it should be possible to run a singleton effect.

simpleAsyncFetch :: MonadIO m => (forall x. f x -> IO x) -> Fetch f m a Source

A simple method of turning an IO bound computation into a concurrent Fetch.

fetchNil :: Applicative m => Fetch (Union `[]`) m a Source

Fetch empty union. Only necessary to terminate a list of Fetch functions for Fetch (Union r)

(|:|) :: forall f r a m. Monad m => (forall a'. Fetch f m a') -> (forall a'. Fetch (Union r) m a') -> Fetch (Union (f : r)) m a infixr 5 Source

Like '(:)' for constructing Fetch (Union (f ': r))

hoistFetch :: Functor m => (forall x. m x -> n x) -> Fetch f m a -> Fetch f n a Source

Hoist a Fetch function into a different result monad.

transFetch :: (forall x. g x -> f x) -> Fetch f m a -> Fetch g m a Source

Translate a Fetch function from f requests, to g requests.

The Sequence of Effects

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.

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.

Caching

newtype CachedFetch f a Source

Caching in Fraxl works by translating FreerT f into FreerT (CachedFetch f), then running with CachedFetch's DataSource. That instance requires f to to have a GCompare instance.

The CachedFetch instance uses a MonadState to track cached requests. The state variable is a DMap from the 'dependent-map' package. Keys are requests, and values are MVars of the results.

Constructors

CachedFetch (f a) 

fetchCached :: forall t m f a. (Monad m, MonadTrans t, MonadState (DMap f MVar) (t m), GCompare f, MonadIO (t m)) => (forall a'. Fetch f m a') -> Fetch (CachedFetch f) (t m) a Source

runCachedFraxl :: forall m f a. (MonadIO m, GCompare f) => (forall a'. Fetch f m a') -> FreerT f m a -> DMap f MVar -> m (a, DMap f MVar) Source

Runs a Fraxl computation with caching using a given starting cache. Alongside the result, it returns the final cache.

evalCachedFraxl :: forall m f a. (MonadIO m, GCompare f) => (forall a'. Fetch f m a') -> FreerT f m a -> m a Source

Like runCachedFraxl, except it starts with an empty cache and discards the final cache.

Union

newtype Union r a Source

FunctorCoRec doesn't implement GCompare. To avoid orphan instances, a newtype is defined.

Union represents a value of any type constructor in r applied with a.

Constructors

Union (FunctorCoRec r a) 

Instances

(GCompare * f, GCompare * (Union r)) => GCompare * (Union ((:) (* -> *) f r)) Source 
GCompare * (Union ([] (* -> *))) Source 
(GEq * f, GEq * (Union r)) => GEq * (Union ((:) (* -> *) f r)) Source 
GEq * (Union ([] (* -> *))) Source 
(Monad m, (∈) (* -> *) f r) => MonadFraxl f (Fraxl r m) Source 

getCoRec :: Union r a -> CoRec (Flap a) r Source

mkUnion :: CoRec (Flap a) r -> Union r a Source