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

Safe HaskellNone
LanguageHaskell2010

Haxl.Core

Contents

Description

Everything needed to define data sources and to invoke the engine.

Synopsis

The monad and operations

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

Instances

Monad (GenHaxl u) Source # 

Methods

(>>=) :: GenHaxl u a -> (a -> GenHaxl u b) -> GenHaxl u b #

(>>) :: GenHaxl u a -> GenHaxl u b -> GenHaxl u b #

return :: a -> GenHaxl u a #

fail :: String -> GenHaxl u a #

Functor (GenHaxl u) Source # 

Methods

fmap :: (a -> b) -> GenHaxl u a -> GenHaxl u b #

(<$) :: a -> GenHaxl u b -> GenHaxl u a #

Applicative (GenHaxl u) Source # 

Methods

pure :: a -> GenHaxl u a #

(<*>) :: GenHaxl u (a -> b) -> GenHaxl u a -> GenHaxl u b #

(*>) :: GenHaxl u a -> GenHaxl u b -> GenHaxl u b #

(<*) :: GenHaxl u a -> GenHaxl u b -> GenHaxl u a #

MonadThrow (GenHaxl u) Source #

Since: 0.3.1.0

Methods

throwM :: Exception e => e -> GenHaxl u a #

MonadCatch (GenHaxl u) Source #

Since: 0.3.1.0

Methods

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

IsString a => IsString (GenHaxl u a) Source # 

Methods

fromString :: String -> GenHaxl u a #

NFData (GenHaxl u a) Source # 

Methods

rnf :: GenHaxl u a -> () #

(~) * u1 u2 => IfThenElse (GenHaxl u1 Bool) (GenHaxl u2 a) Source # 

Methods

ifThenElse :: GenHaxl u1 Bool -> GenHaxl u2 a -> GenHaxl u2 a -> GenHaxl u2 a Source #

runHaxl :: Env u -> GenHaxl u a -> IO a Source #

Runs a Haxl computation in an Env.

Env

data Env u Source #

The data we carry around in the Haxl monad.

Constructors

Env 

Fields

type Caches u = (IORef (DataCache ResultVar), IORef (DataCache (MemoVar u))) Source #

Operations in the monad

env :: (Env u -> a) -> GenHaxl u a Source #

Extracts data from the Env.

withEnv :: Env u -> GenHaxl u a -> GenHaxl u a Source #

Returns a version of the Haxl computation which always uses the provided Env, ignoring the one specified by runHaxl.

withLabel :: ProfileLabel -> GenHaxl u a -> GenHaxl u a Source #

Label a computation so profiling data is attributed to the label.

Building the Env

initEnvWithData :: StateStore -> u -> Caches u -> IO (Env u) Source #

Initialize an environment with a StateStore, an input map, a preexisting DataCache, and a seed for the random number generator.

initEnv :: StateStore -> u -> IO (Env u) Source #

Initializes an environment with StateStore and an input map.

emptyEnv :: u -> IO (Env u) Source #

A new, empty environment.

Building the StateStore

data StateStore Source #

The StateStore maps a StateKey to the State for that type.

stateGet :: forall r. StateKey r => StateStore -> Maybe (State r) Source #

Retrieves a State from the StateStore container.

stateSet :: forall f. StateKey f => State f -> StateStore -> StateStore Source #

Inserts a State in the StateStore container.

stateEmpty :: StateStore Source #

A StateStore with no entries.

Exceptions

throw :: Exception e => e -> GenHaxl u a Source #

Throw an exception in the Haxl monad

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

Catch an exception in the Haxl monad

catchIf :: Exception e => (e -> Bool) -> GenHaxl u a -> (e -> GenHaxl u a) -> GenHaxl u a Source #

Catch exceptions that satisfy a predicate

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

Returns Left e if the computation throws an exception e, or Right a if it returns a result a.

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 a Source #

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

uncachedRequest :: (DataSource u r, Show (r a)) => r a -> GenHaxl u a Source #

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 a Source #

Transparently provides caching. Useful for datasources that can return immediately, but also caches values. Exceptions thrown by the IO operation (except for asynchronous exceptions) are propagated into the Haxl monad and can be caught by catch and try.

cachedComputation :: forall req u a. (Eq (req a), Hashable (req a), Typeable (req a)) => req a -> GenHaxl u a -> GenHaxl u a Source #

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 String Source #

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))

Memoization

memo :: (Typeable a, Typeable k, Hashable k, Eq k) => k -> GenHaxl u a -> GenHaxl u a Source #

Memoize a computation using an arbitrary key. The result will be calculated once; the second and subsequent time it will be returned immediately. It is the caller's responsibility to ensure that for every two calls memo key haxl, if they have the same key then they compute the same result.

memoize :: GenHaxl u a -> GenHaxl u a Source #

Transform a Haxl computation into a memoized version of itself.

Given a Haxl computation, memoize creates a version which stores its result in a MemoVar (which memoize creates), and returns the stored result on subsequent invocations. This permits the creation of local memos, whose lifetimes are scoped to the current function, rather than the entire request.

memoize1 :: (Eq a, Hashable a) => (a -> GenHaxl u b) -> GenHaxl u (a -> GenHaxl u b) Source #

Transform a 1-argument function returning a Haxl computation into a memoized version of itself.

Given a function f of type a -> GenHaxl u b, memoize1 creates a version which memoizes the results of f in a table keyed by its argument, and returns stored results on subsequent invocations with the same argument.

e.g.:

allFriends :: [Int] -> GenHaxl u [Int] allFriends ids = do memoizedFriendsOf <- memoize1 friendsOf concat $ mapM memoizeFriendsOf ids

The above implementation will not invoke the underlying friendsOf repeatedly for duplicate values in ids.

memoize2 :: (Eq a, Hashable a, Eq b, Hashable b) => (a -> b -> GenHaxl u c) -> GenHaxl u (a -> b -> GenHaxl u c) Source #

Transform a 2-argument function returning a Haxl computation, into a memoized version of itself.

The 2-ary version of memoize1, see its documentation for details.

data MemoFingerprintKey a where Source #

A memo key derived from a 128-bit MD5 hash. Do not use this directly, it is for use by automatically-generated memoization.

Statistics

newtype Stats Source #

Stats that we collect along the way.

Constructors

Stats [RoundStats] 

data RoundStats Source #

Maps data source name to the number of requests made in that round. The map only contains entries for sources that made requests in that round.

Constructors

RoundStats

Timing stats for a round of data fetching

FetchCall

The stack trace of a call to dataFetch. These are collected only when profiling and reportLevel is 5 or greater.

Fields

ppStats :: Stats -> String Source #

Pretty-print Stats.

ppRoundStats :: RoundStats -> String Source #

Pretty-print RoundStats.

ppDataSourceRoundStats :: DataSourceRoundStats -> String Source #

Pretty-print DataSourceRoundStats

profile :: Profile -> HashMap ProfileLabel ProfileData Source #

Data on individual labels.

profileRound :: Profile -> Round Source #

Keep track of what the current fetch round is.

profileCache :: Profile -> DataCache (Constant Round) Source #

Keep track of the round requests first appear in.

data ProfileData Source #

Constructors

ProfileData 

Fields

Tracing flags

data Flags Source #

Flags that control the operation of the engine.

Constructors

Flags 

Fields

  • trace :: !Int

    Tracing level (0 = quiet, 3 = very verbose).

  • report :: !Int

    Report level (0 = quiet, 1 = of errors, 4 = profiling, 5 = log stack traces of dataFetch calls)

  • caching :: !Int

    Non-zero if caching is enabled. If caching is disabled, then we still do batching and de-duplication within a round, but do not cache results between rounds.

ifTrace :: (Functor m, Monad m) => Flags -> Int -> m a -> m () Source #

Runs an action if the tracing level is above the given threshold.

ifReport :: (Functor m, Monad m) => Flags -> Int -> m a -> m () Source #

Runs an action if the report level is above the given threshold.

ifProfiling :: (Functor m, Monad m) => Flags -> m a -> m () Source #

Building data sources

class (DataSourceName req, StateKey req, Show1 req) => DataSource u req where Source #

The class of data sources, parameterised over the request type for that data source. Every data source must implement this class.

A data source keeps track of its state by creating an instance of StateKey to map the request type to its state. In this case, the type of the state should probably be a reference type of some kind, such as IORef.

For a complete example data source, see Examples.

Minimal complete definition

fetch

Methods

fetch :: State req -> Flags -> u -> [BlockedFetch req] -> PerformFetch Source #

Issues a list of fetches to this DataSource. The BlockedFetch objects contain both the request and the ResultVars into which to put the results.

class Show1 f where Source #

A class of type constructors for which we can show all parameterizations.

Minimal complete definition

show1

Methods

show1 :: f a -> String Source #

class DataSourceName req where Source #

Minimal complete definition

dataSourceName

Methods

dataSourceName :: req a -> Text Source #

The name of this DataSource, used in tracing and stats. Must take a dummy request.

type Request req a = (Eq (req a), Hashable (req a), Typeable (req a), Show (req a), Show a) Source #

A convenience only: package up Eq, Hashable, Typeable, and Show for requests into a single constraint.

data BlockedFetch r Source #

A BlockedFetch is a pair of

  • The request to fetch (with result type a)
  • A ResultVar to store either the result or an error

We often want to collect together multiple requests, but they return different types, and the type system wouldn't let us put them together in a list because all the elements of the list must have the same type. So we wrap up these types inside the BlockedFetch type, so that they all look the same and we can put them in a list.

When we unpack the BlockedFetch and get the request and the ResultVar out, the type system knows that the result type of the request matches the type parameter of the ResultVar, so it will let us take the result of the request and store it in the ResultVar.

Constructors

BlockedFetch (r a) (ResultVar a) 

data PerformFetch Source #

A data source can fetch data in one of two ways.

  • Synchronously (SyncFetch): the fetching operation is an IO () that fetches all the data and then returns.
  • Asynchronously (AsyncFetch): we can do something else while the data is being fetched. The fetching operation takes an IO () as an argument, which is the operation to perform while the data is being fetched.

See syncFetch and asyncFetch for example usage.

Constructors

SyncFetch (IO ()) 
AsyncFetch (IO () -> IO ()) 

class Typeable f => StateKey f Source #

StateKey maps one type to another type. A type that is an instance of StateKey can store and retrieve information from a StateStore.

Associated Types

data State f Source #

Result variables

newtype ResultVar a Source #

A sink for the result of a data fetch in BlockedFetch

Constructors

ResultVar (MVar (Either SomeException a)) 

putFailure :: Exception e => ResultVar a -> e -> IO () Source #

putSuccess :: ResultVar a -> a -> IO () Source #

Default fetch implementations

asyncFetch Source #

Arguments

:: ((service -> IO ()) -> IO ())

Wrapper to perform an action in the context of a service.

-> (service -> IO ())

Dispatch all the pending requests and wait for the results

-> (forall a. service -> request a -> IO (IO (Either SomeException a)))

Submits an individual request to the service.

-> State request

Currently unused.

-> Flags

Currently unused.

-> u

Currently unused.

-> [BlockedFetch request]

Requests to submit.

-> PerformFetch 

asyncFetchWithDispatch Source #

Arguments

:: ((service -> IO ()) -> IO ())

Wrapper to perform an action in the context of a service.

-> (service -> IO ())

Dispatch all the pending requests

-> (service -> IO ())

Wait for the results

-> (forall a. service -> request a -> IO (IO (Either SomeException a)))

Enqueue an individual request to the service.

-> State request

Currently unused.

-> Flags

Currently unused.

-> u

Currently unused.

-> [BlockedFetch request]

Requests to submit.

-> PerformFetch 

Common implementation templates for fetch of DataSource.

Example usage:

fetch = syncFetch MyDS.withService MyDS.retrieve
  $ \service request -> case request of
    This x -> MyDS.fetchThis service x
    That y -> MyDS.fetchThat service y

stubFetch :: Exception e => (forall a. r a -> e) -> State r -> Flags -> u -> [BlockedFetch r] -> PerformFetch Source #

syncFetch Source #

Arguments

:: ((service -> IO ()) -> IO ())

Wrapper to perform an action in the context of a service.

-> (service -> IO ())

Dispatch all the pending requests and wait for the results

-> (forall a. service -> request a -> IO (IO (Either SomeException a)))

Submits an individual request to the service.

-> State request

Currently unused.

-> Flags

Currently unused.

-> u

Currently unused.

-> [BlockedFetch request]

Requests to submit.

-> PerformFetch 

Utilities

setError :: Exception e => (forall a. r a -> e) -> BlockedFetch r -> IO () Source #

Function for easily setting a fetch to a particular exception

Exceptions