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

Safe HaskellNone

Haxl.Core.Types

Contents

Description

Base types used by all of Haxl.

Synopsis

Initialization strategies

data InitStrategy Source

Initialization strategy. FullInit will do as much initialization as possible. FastInit will postpone part of initialization or omit part of initialization by sharing more resources. Use FastInit if you want fast initialization but don't care much about performance, for example, in interactive environment.

Constructors

FullInit 
FastInit 

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

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

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

Statistics

newtype Stats Source

Stats that we collect along the way.

Constructors

Stats [RoundStats] 

Instances

newtype 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 (HashMap Text Int) 

Instances

Data fetching

class (DataSourceName req, StateKey req, Show1 req) => DataSource u req whereSource

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 ExampleDataSource.

Methods

fetchSource

Arguments

:: State req

Current state.

-> Flags

Tracing flags.

-> u

User environment.

-> [BlockedFetch req]

Requests to fetch.

-> PerformFetch

Fetch the data; see PerformFetch.

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

class DataSourceName req whereSource

Methods

dataSourceName :: req a -> TextSource

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)
  • An MVar 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 MVar out, the type system knows that the result type of the request matches the type parameter of the MVar, so it will let us take the result of the request and store it in the MVar.

Constructors

forall a . 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 ()) 

Result variables

newtype ResultVar a Source

A sink for the result of a data fetch, used by BlockedFetch and the DataCache. Why do we need an MVar here? The reason is that the cache serves two purposes:

  1. To cache the results of requests that were submitted in a previous round.
  2. To remember requests that have been encountered in the current round but are not yet submitted, so that if we see the request again we can make sure that we only submit it once.

Storing the result as an MVar gives two benefits:

  • We can tell the difference between (1) and (2) by testing whether the MVar is empty. See cached.
  • In the case of (2), we don't have to update the cache again after the current round, and after the round we can read the result of each request from its MVar. All instances of identical requests will share the same MVar to obtain the result.

Constructors

ResultVar (MVar (Either SomeException a)) 

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

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

Default fetch implementations

asyncFetchSource

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 

asyncFetchWithDispatchSource

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] -> PerformFetchSource

syncFetchSource

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