Safe Haskell | None |
---|---|
Language | Haskell2010 |
Everything needed to define data sources and to invoke the engine.
- newtype GenHaxl u a = GenHaxl {
- unHaxl :: Env u -> IORef (RequestStore u) -> IO (Result u a)
- runHaxl :: Env u -> GenHaxl u a -> IO a
- data Env u = Env {}
- type Caches u = (IORef (DataCache ResultVar), IORef (DataCache (MemoVar u)))
- caches :: Env u -> Caches u
- env :: (Env u -> a) -> GenHaxl u a
- withEnv :: Env u -> GenHaxl u a -> GenHaxl u a
- withLabel :: ProfileLabel -> GenHaxl u a -> GenHaxl u a
- initEnvWithData :: StateStore -> u -> Caches u -> IO (Env u)
- initEnv :: StateStore -> u -> IO (Env u)
- emptyEnv :: u -> IO (Env u)
- data StateStore
- stateGet :: forall r. StateKey r => StateStore -> Maybe (State r)
- stateSet :: forall f. StateKey f => State f -> StateStore -> StateStore
- stateEmpty :: StateStore
- throw :: Exception e => e -> GenHaxl u a
- catch :: Exception e => GenHaxl u a -> (e -> GenHaxl u a) -> GenHaxl u a
- catchIf :: Exception e => (e -> Bool) -> GenHaxl u a -> (e -> GenHaxl u a) -> GenHaxl u a
- try :: Exception e => GenHaxl u a -> GenHaxl u (Either e a)
- tryToHaxlException :: GenHaxl u a -> GenHaxl u (Either HaxlException a)
- dataFetch :: (DataSource u r, Request r a) => r a -> GenHaxl u a
- uncachedRequest :: (DataSource u r, Show (r a)) => r a -> GenHaxl u a
- cacheRequest :: Request req a => req a -> Either SomeException a -> GenHaxl u ()
- cacheResult :: Request r a => r a -> IO a -> GenHaxl u a
- cacheResultWithShow :: (Eq (r a), Hashable (r a), Typeable (r a)) => ShowReq r a -> r a -> IO a -> GenHaxl u a
- cachedComputation :: forall req u a. (Eq (req a), Hashable (req a), Typeable (req a)) => req a -> GenHaxl u a -> GenHaxl u a
- dumpCacheAsHaskell :: GenHaxl u String
- memo :: (Typeable a, Typeable k, Hashable k, Eq k) => k -> GenHaxl u a -> GenHaxl u a
- memoize :: GenHaxl u a -> GenHaxl u a
- memoize1 :: (Eq a, Hashable a) => (a -> GenHaxl u b) -> GenHaxl u (a -> GenHaxl u b)
- memoize2 :: (Eq a, Hashable a, Eq b, Hashable b) => (a -> b -> GenHaxl u c) -> GenHaxl u (a -> b -> GenHaxl u c)
- memoFingerprint :: Typeable a => MemoFingerprintKey a -> GenHaxl u a -> GenHaxl u a
- data MemoFingerprintKey a where
- MemoFingerprintKey :: !Word64 -> !Word64 -> Addr# -> Addr# -> MemoFingerprintKey a
- pAnd :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool
- pOr :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool
- newtype Stats = Stats [RoundStats]
- data RoundStats
- = RoundStats { }
- | FetchCall {
- fetchReq :: String
- fetchStack :: [String]
- data DataSourceRoundStats = DataSourceRoundStats {}
- type Microseconds = Int
- emptyStats :: Stats
- numRounds :: Stats -> Int
- numFetches :: Stats -> Int
- ppStats :: Stats -> String
- ppRoundStats :: RoundStats -> String
- ppDataSourceRoundStats :: DataSourceRoundStats -> String
- data Profile
- emptyProfile :: Profile
- profile :: Profile -> HashMap ProfileLabel ProfileData
- profileRound :: Profile -> Round
- profileCache :: Profile -> DataCache (Constant Round)
- type ProfileLabel = Text
- data ProfileData = ProfileData {}
- emptyProfileData :: ProfileData
- data Flags = Flags {}
- defaultFlags :: Flags
- ifTrace :: Monad m => Flags -> Int -> m a -> m ()
- ifReport :: Monad m => Flags -> Int -> m a -> m ()
- ifProfiling :: Monad m => Flags -> m a -> m ()
- class (DataSourceName req, StateKey req, ShowP req) => DataSource u req where
- class ShowP f where
- class DataSourceName req where
- type Request req a = (Eq (req a), Hashable (req a), Typeable (req a), Show (req a), Show a)
- data BlockedFetch r = BlockedFetch (r a) (ResultVar a)
- data PerformFetch
- = SyncFetch (IO ())
- | AsyncFetch (IO () -> IO ())
- class Typeable f => StateKey f where
- data State f
- newtype ResultVar a = ResultVar (MVar (Either SomeException a))
- newEmptyResult :: IO (ResultVar a)
- newResult :: a -> IO (ResultVar a)
- putFailure :: Exception e => ResultVar a -> e -> IO ()
- putResult :: ResultVar a -> Either SomeException a -> IO ()
- putSuccess :: ResultVar a -> a -> IO ()
- takeResult :: ResultVar a -> IO (Either SomeException a)
- tryReadResult :: ResultVar a -> IO (Maybe (Either SomeException a))
- tryTakeResult :: ResultVar a -> IO (Maybe (Either SomeException a))
- asyncFetch :: ((service -> IO ()) -> IO ()) -> (service -> IO ()) -> (forall a. service -> request a -> IO (IO (Either SomeException a))) -> State request -> Flags -> u -> [BlockedFetch request] -> PerformFetch
- asyncFetchWithDispatch :: ((service -> IO ()) -> IO ()) -> (service -> IO ()) -> (service -> IO ()) -> (forall a. service -> request a -> IO (IO (Either SomeException a))) -> State request -> Flags -> u -> [BlockedFetch request] -> PerformFetch
- asyncFetchAcquireRelease :: IO service -> (service -> IO ()) -> (service -> IO ()) -> (service -> IO ()) -> (forall a. service -> request a -> IO (IO (Either SomeException a))) -> State request -> Flags -> u -> [BlockedFetch request] -> PerformFetch
- stubFetch :: Exception e => (forall a. r a -> e) -> State r -> Flags -> u -> [BlockedFetch r] -> PerformFetch
- syncFetch :: ((service -> IO ()) -> IO ()) -> (service -> IO ()) -> (forall a. service -> request a -> IO (IO (Either SomeException a))) -> State request -> Flags -> u -> [BlockedFetch request] -> PerformFetch
- except :: Exception e => e -> Either SomeException a
- setError :: Exception e => (forall a. r a -> e) -> BlockedFetch r -> IO ()
- module Haxl.Core.Exception
The monad and operations
The Haxl monad, which does several things:
- It is a reader monad for
Env
andIORef
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 theRequestStore
, and then resume the computation. - The Applicative combinator
<*>
explores both branches in the event that the left branch isBlocked
, so that we can collect multiple requests and submit them as a batch. - It contains IO, so that we can perform real data fetching.
Env
The data we carry around in the Haxl monad.
Env | |
|
Operations in the monad
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.
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
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
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.
cacheResultWithShow :: (Eq (r a), Hashable (r a), Typeable (r a)) => ShowReq r a -> r a -> IO a -> GenHaxl u a Source #
Transparently provides caching in the same way as cacheResult
, but uses
the given functions to show requests and their results.
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.
memoFingerprint :: Typeable a => MemoFingerprintKey a -> GenHaxl u a -> GenHaxl u a Source #
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.
MemoFingerprintKey :: !Word64 -> !Word64 -> Addr# -> Addr# -> MemoFingerprintKey a |
Eq (MemoFingerprintKey a) Source # | |
Hashable (MemoFingerprintKey a) Source # | |
Conditionals
pAnd :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool infixr 5 Source #
Parallel version of '(.&&)'. Both arguments are evaluated in
parallel, and if either returns False
then the other is
not evaluated any further.
WARNING: exceptions may be unpredictable when using pAnd
. If one
argument returns False
before the other completes, then pAnd
returns False
immediately, ignoring a possible exception that
the other argument may have produced if it had been allowed to
complete.
pOr :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool infixr 4 Source #
Parallel version of '(.||)'. Both arguments are evaluated in
parallel, and if either returns True
then the other is
not evaluated any further.
WARNING: exceptions may be unpredictable when using pOr
. If one
argument returns True
before the other completes, then pOr
returns True
immediately, ignoring a possible exception that
the other argument may have produced if it had been allowed to
complete.
Statistics
Stats that we collect along the way.
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.
RoundStats | Timing stats for a round of data fetching |
FetchCall | The stack trace of a call to |
|
data DataSourceRoundStats Source #
Detailed stats of each data source in each round.
type Microseconds = Int Source #
emptyStats :: Stats Source #
numFetches :: Stats -> Int Source #
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.
type ProfileLabel = Text Source #
data ProfileData Source #
ProfileData | |
|
Tracing flags
Flags that control the operation of the engine.
defaultFlags :: Flags Source #
ifTrace :: Monad m => Flags -> Int -> m a -> m () Source #
Runs an action if the tracing level is above the given threshold.
ifReport :: Monad m => Flags -> Int -> m a -> m () Source #
Runs an action if the report level is above the given threshold.
ifProfiling :: Monad m => Flags -> m a -> m () Source #
Building data sources
class (DataSourceName req, StateKey req, ShowP 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.
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 ResultVar
s into which to put
the results.
A class of type constructors for which we can show all parameterizations.
class DataSourceName req where Source #
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 #
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
.
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
that fetches all the data and then returns.IO
() - Asynchronously (
AsyncFetch
): we can do something else while the data is being fetched. The fetching operation takes an
as an argument, which is the operation to perform while the data is being fetched.IO
()
See syncFetch
and asyncFetch
for example usage.
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
.
Result variables
A sink for the result of a data fetch in BlockedFetch
ResultVar (MVar (Either SomeException a)) |
newEmptyResult :: IO (ResultVar a) Source #
putSuccess :: ResultVar a -> a -> IO () Source #
takeResult :: ResultVar a -> IO (Either SomeException a) Source #
tryReadResult :: ResultVar a -> IO (Maybe (Either SomeException a)) Source #
tryTakeResult :: ResultVar a -> IO (Maybe (Either SomeException a)) Source #
Default fetch implementations
:: ((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 #
:: ((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
asyncFetchAcquireRelease Source #
:: IO service | Resource acquisition for this datasource |
-> (service -> IO ()) | Resource release |
-> (service -> IO ()) | Dispatch all the pending requests and wait for the results |
-> (service -> IO ()) | 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 |
A version of asyncFetch
(actually asyncFetchWithDispatch
) that
handles exceptions correctly. You should use this instead of
asyncFetch
or asyncFetchWithDispatch
. The danger with
asyncFetch
is that if an exception is thrown by withService
, the
inner
action won't be executed, and we'll drop some data-fetches in
the same round.
asyncFetchAcquireRelease
behaves like the following:
asyncFetchAcquireRelease acquire release dispatch wait enqueue = AsyncFetch $ \inner -> bracket acquire release $ \service -> do getResults <- mapM (submitFetch service enqueue) requests dispatch service inner wait service sequence_ getResults
except that inner
is run even if acquire
, enqueue
, or dispatch
throws,
unless an async exception is received.
stubFetch :: Exception e => (forall a. r a -> e) -> State r -> Flags -> u -> [BlockedFetch r] -> PerformFetch Source #
:: ((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
module Haxl.Core.Exception