Safe Haskell | None |
---|---|
Language | Haskell2010 |
The implementation of the Haxl
monad. Most users should
import Haxl.Core instead of importing this module directly.
- newtype GenHaxl u a = GenHaxl {}
- data Result u a
- data Cont u a
- toHaxl :: Cont u a -> GenHaxl u a
- newtype IVar u a = IVar (IORef (IVarContents u a))
- data IVarContents u a
- newIVar :: IO (IVar u a)
- newFullIVar :: ResultVal a -> IO (IVar u a)
- getIVar :: IVar u a -> GenHaxl u a
- putIVar :: IVar u a -> ResultVal a -> Env u -> IO ()
- data ResultVal a
- done :: ResultVal a -> IO (Result u a)
- eitherToResult :: Either SomeException a -> ResultVal a
- eitherToResultThrowIO :: Either SomeException a -> ResultVal a
- data CompleteReq u = CompleteReq (Either SomeException a) !(IVar u a) !Int64
- data Env u = Env {
- cacheRef :: !(IORef (DataCache (IVar u)))
- memoRef :: !(IORef (DataCache (IVar u)))
- flags :: !Flags
- userEnv :: u
- statsRef :: !(IORef Stats)
- profLabel :: ProfileLabel
- profRef :: !(IORef Profile)
- states :: StateStore
- reqStoreRef :: !(IORef (RequestStore u))
- runQueueRef :: !(IORef (JobList u))
- completions :: !(TVar [CompleteReq u])
- pendingWaits :: [IO ()]
- speculative :: !Int
- type Caches u = (IORef (DataCache (IVar u)), IORef (DataCache (IVar u)))
- caches :: Env u -> Caches u
- initEnvWithData :: StateStore -> u -> Caches u -> IO (Env u)
- initEnv :: StateStore -> u -> IO (Env u)
- emptyEnv :: u -> IO (Env u)
- env :: (Env u -> a) -> GenHaxl u a
- withEnv :: Env u -> GenHaxl u a -> GenHaxl u a
- speculate :: Env u -> Env u
- imperative :: Env u -> Env u
- data JobList u
- appendJobList :: JobList u -> JobList u -> JobList u
- lengthJobList :: JobList u -> Int
- addJob :: Env u -> GenHaxl u b -> IVar u b -> IVar u a -> IO ()
- throw :: Exception e => e -> GenHaxl u a
- raise :: Exception e => e -> IO (Result 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)
- dumpCacheAsHaskell :: GenHaxl u String
- dumpCacheAsHaskellFn :: String -> String -> GenHaxl u String
- unsafeLiftIO :: IO a -> GenHaxl u a
- unsafeToHaxlException :: GenHaxl u a -> GenHaxl u a
The monad
The Haxl monad, which does several things:
- It is a reader monad for
Env
, which contains the current state of the scheduler, including unfetched requests and the run queue of computations. - 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.
The result of a computation is either Done
with a value, Throw
with an exception, or Blocked
on the result of a data fetch with
a continuation.
Cont
A data representation of a Haxl continuation. This is to avoid repeatedly traversing a left-biased tree in a continuation, leading O(n^2) complexity for some pathalogical cases - see the "seql" benchmark in tests/MonadBench.hs. See "A Smart View on Datatypes", Jaskelioff/Rivas, ICFP'15
IVar
A synchronisation point. It either contains a value, or a list of computations waiting for the value.
IVar (IORef (IVarContents u a)) |
ResultVal
The contents of a full IVar. We have to distinguish exceptions thrown in the IO monad from exceptions thrown in the Haxl monad, so that when the result is fetched using getIVar, we can throw the exception in the right way.
eitherToResult :: Either SomeException a -> ResultVal a Source #
eitherToResultThrowIO :: Either SomeException a -> ResultVal a Source #
CompleteReq
data CompleteReq u Source #
A completed request from a data source, containing the result,
and the IVar
representing the blocked computations. The job of a
data source is just to add these to a queue (completions
) using
putResult
; the scheduler collects them from the queue and unblocks
the relevant computations.
CompleteReq (Either SomeException a) !(IVar u a) !Int64 |
Env
The data we carry around in the Haxl monad.
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.
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
.
imperative :: Env u -> Env u Source #
JobList
A list of computations together with the IVar into which they should put their result.
This could be an ordinary list, but the optimised representation saves space and time.
lengthJobList :: JobList u -> Int Source #
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.
Dumping the cache
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.
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.