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

Safe HaskellNone
LanguageHaskell2010

Haxl.Core.Types

Contents

Description

Base types used by all of Haxl. Most users should import Haxl.Core instead of importing this module directly.

Synopsis

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 #

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

type Round = Int Source #

Rounds are 1-indexed

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

Data fetching

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

DataCache

newtype DataCache res Source #

The DataCache maps things of type f a to ResultVar a, for any f and a provided f a is an instance of Typeable. In practice f a will be a request type parameterised by its result.

See the definition of ResultVar for more details.

Constructors

DataCache (HashMap TypeRep (SubCache res)) 

data SubCache res Source #

The implementation is a two-level map: the outer level maps the types of requests to SubCache, which maps actual requests to their results. So each SubCache contains requests of the same type. This works well because we only have to store the dictionaries for Hashable and Eq once per request type.

Constructors

(Hashable (req a), Eq (req a), Typeable (req a)) => SubCache (req a -> String) (a -> String) !(HashMap (req a) (res a)) 

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