haxl-0.1.0.0: A Haskell library for efficient, concurrent, and concise data access.

Safe HaskellNone

Haxl.Core.Monad

Contents

Description

The implementation of the Haxl monad.

Synopsis

The monad

newtype GenHaxl u a Source

The Haxl monad, which does several things:

  • It is a reader monad for Env and IORef RequestStore, The latter is the current batch of unsubmitted data fetch requests.
  • It is a concurrency, or resumption, monad. A computation may run partially and return Blocked, in which case the framework should perform the outstanding requests in the RequestStore, and then resume the computation.
  • The Applicative combinator <*> explores both branches in the event that the left branch is Blocked, so that we can collect multiple requests and submit them as a batch.
  • It contains IO, so that we can perform real data fetching.

Constructors

GenHaxl 

Fields

unHaxl :: Env u -> IORef (RequestStore u) -> IO (Result u a)
 

Instances

Monad (GenHaxl u) 
Functor (GenHaxl u) 
Applicative (GenHaxl u) 
Fractional a => Fractional (GenHaxl u a) 
Num a => Num (GenHaxl u a) 
IsString a => IsString (GenHaxl u a) 
~ * u1 u2 => IfThenElse (GenHaxl u1 Bool) (GenHaxl u2 a) 

runHaxl :: Env u -> GenHaxl u a -> IO aSource

Runs a Haxl computation in an Env.

env :: (Env u -> a) -> GenHaxl u aSource

Extracts data from the Env.

Exceptions

throw :: Exception e => e -> GenHaxl u aSource

Throw an exception in the Haxl monad

catch :: Exception e => GenHaxl u a -> (e -> GenHaxl u a) -> GenHaxl u aSource

try :: Exception e => GenHaxl u a -> GenHaxl u (Either e a)Source

tryToHaxlException :: GenHaxl u a -> GenHaxl u (Either HaxlException a)Source

Like try, but lifts all exceptions into the HaxlException hierarchy. Uses unsafeToHaxlException internally. Typically this is used at the top level of a Haxl computation, to ensure that all exceptions are caught.

Data fetching and caching

dataFetch :: (DataSource u r, Request r a) => r a -> GenHaxl u aSource

Performs actual fetching of data for a Request from a DataSource.

uncachedRequest :: (DataSource u r, Request r a) => r a -> GenHaxl u aSource

A data request that is not cached. This is not what you want for normal read requests, because then multiple identical requests may return different results, and this invalidates some of the properties that we expect Haxl computations to respect: that data fetches can be aribtrarily reordered, and identical requests can be commoned up, for example.

uncachedRequest is useful for performing writes, provided those are done in a safe way - that is, not mixed with reads that might conflict in the same Haxl computation.

cacheRequest :: Request req a => req a -> Either SomeException a -> GenHaxl u ()Source

Inserts a request/result pair into the cache. Throws an exception if the request has already been issued, either via dataFetch or cacheRequest.

This can be used to pre-populate the cache when running tests, to avoid going to the actual data source and ensure that results are deterministic.

cacheResult :: Request r a => r a -> IO a -> GenHaxl u aSource

Transparently provides caching. Useful for datasources that can return immediately, but also caches values.

cachedComputation :: forall req u a. Request req a => req a -> GenHaxl u a -> GenHaxl u aSource

cachedComputation memoizes a Haxl computation. The key is a request.

Note: These cached computations will not be included in the output of dumpCacheAsHaskell.

dumpCacheAsHaskell :: GenHaxl u StringSource

Dump the contents of the cache as Haskell code that, when compiled and run, will recreate the same cache contents. For example, the generated code looks something like this:

 loadCache :: GenHaxl u ()
 loadCache = do
   cacheRequest (ListWombats 3) (Right ([1,2,3]))
   cacheRequest (CountAardvarks "abcabc") (Right (2))

Unsafe operations

unsafeLiftIO :: IO a -> GenHaxl u aSource

Under ordinary circumstances this is unnecessary; users of the Haxl monad should generally not perform arbitrary IO.

unsafeToHaxlException :: GenHaxl u a -> GenHaxl u aSource

Convert exceptions in the underlying IO monad to exceptions in the Haxl monad. This is morally unsafe, because you could then catch those exceptions in Haxl and observe the underlying execution order. Not to be exposed to user code.