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

Safe HaskellNone
LanguageHaskell2010

Haxl.Core.Monad

Contents

Description

The implementation of the Haxl monad. Most users should import Haxl.Core instead of importing this module directly.

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) Source 
Functor (GenHaxl u) Source 
Applicative (GenHaxl u) Source 
MonadThrow (GenHaxl u) Source

Since: 0.3.1.0

MonadCatch (GenHaxl u) Source

Since: 0.3.1.0

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

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

Runs a Haxl computation in an Env.

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.

withFingerprintLabel :: Addr# -> Addr# -> GenHaxl u a -> GenHaxl u a Source

Label a computation so profiling data is attributed to the label. Intended only for internal use by memoFingerprint.

Env

data Env u Source

The data we carry around in the Haxl monad.

Constructors

Env 

Fields

cacheRef :: !(IORef (DataCache ResultVar))
 
memoRef :: !(IORef (DataCache (MemoVar u)))
 
flags :: !Flags
 
userEnv :: u
 
statsRef :: !(IORef Stats)
 
profLabel :: ProfileLabel
 
profRef :: !(IORef Profile)
 
states :: StateStore

Data sources and other components can store their state in here. Items in this store must be instances of StateKey.

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

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.

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

type ShowReq r a = (r a -> String, a -> String) Source

Show functions for request and its result.

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

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

dataFetchWithShow :: (DataSource u r, Eq (r a), Hashable (r a), Typeable (r a)) => ShowReq r a -> r a -> GenHaxl u a Source

Performs actual fetching of data for a Request from a DataSource, using the given show functions for requests and their results.

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.

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

dumpCacheAsHaskellFn :: String -> String -> GenHaxl u String Source

Dump the contents of the cache as Haskell code that, when compiled and run, will recreate the same cache contents.

Takes the name and type for the resulting function as arguments.

Memoization Machinery

newMemo :: GenHaxl u (MemoVar u a) Source

Create a new MemoVar for storing a memoized computation. The created MemoVar is initially empty, not tied to any specific computation. Running this memo (with runMemo) without preparing it first (with prepareMemo) will result in an exception.

newMemoWith :: GenHaxl u a -> GenHaxl u (MemoVar u a) Source

Convenience function, combines newMemo and prepareMemo.

prepareMemo :: MemoVar u a -> GenHaxl u a -> GenHaxl u () Source

Store a computation within a supplied MemoVar. Any memo stored within the MemoVar already (regardless of completion) will be discarded, in favor of the supplied computation. A MemoVar must be prepared before it is run.

runMemo :: MemoVar u a -> GenHaxl u a Source

Continue the memoized computation within a given MemoVar. Notes:

  1. If the memo contains a complete result, return that result.
  2. If the memo contains an in-progress computation, continue it as far as possible for this round.
  3. If the memo is empty (it was not prepared), throw an error.

For example, to memoize the computation one given by:

one :: Haxl Int
one = return 1

use:

do
  oneMemo <- newMemoWith one
  let memoizedOne = runMemo aMemo one
  oneResult <- memoizedOne

To memoize mutually dependent computations such as in:

h :: Haxl Int
h = do
  a <- f
  b <- g
  return (a + b)
 where
  f = return 42
  g = succ <$> f

without needing to reorder them, use:

h :: Haxl Int
h = do
  fMemoRef <- newMemo
  gMemoRef <- newMemo

  let f = runMemo fMemoRef
      g = runMemo gMemoRef

  prepareMemo fMemoRef $ return 42
  prepareMemo gMemoRef $ succ <$> f

  a <- f
  b <- g
  return (a + b)

newMemo1 :: GenHaxl u (MemoVar1 u a b) Source

newMemoWith1 :: (a -> GenHaxl u b) -> GenHaxl u (MemoVar1 u a b) Source

prepareMemo1 :: MemoVar1 u a b -> (a -> GenHaxl u b) -> GenHaxl u () Source

runMemo1 :: (Eq a, Hashable a) => MemoVar1 u a b -> a -> GenHaxl u b Source

newMemo2 :: GenHaxl u (MemoVar2 u a b c) Source

newMemoWith2 :: (a -> b -> GenHaxl u c) -> GenHaxl u (MemoVar2 u a b c) Source

prepareMemo2 :: MemoVar2 u a b c -> (a -> b -> GenHaxl u c) -> GenHaxl u () Source

runMemo2 :: (Eq a, Hashable a, Eq b, Hashable b) => MemoVar2 u a b c -> a -> b -> GenHaxl u c Source

Unsafe operations

unsafeLiftIO :: IO a -> GenHaxl u a Source

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

unsafeToHaxlException :: GenHaxl u a -> GenHaxl u a Source

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.