| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Haxl.Core.Types
Contents
Description
Base types used by all of Haxl. Most users should import Haxl.Core instead of importing this module directly.
- data Flags = Flags {}
 - defaultFlags :: Flags
 - ifTrace :: (Functor m, Monad m) => Flags -> Int -> m a -> m ()
 - ifReport :: (Functor m, Monad m) => Flags -> Int -> m a -> m ()
 - ifProfiling :: (Functor m, Monad m) => Flags -> m a -> m ()
 - newtype Stats = Stats [RoundStats]
 - data RoundStats
- = RoundStats { }
 - | FetchCall { 
- fetchReq :: String
 - fetchStack :: [String]
 
 
 - data DataSourceRoundStats = DataSourceRoundStats {}
 - type Microseconds = Int
 - type Round = 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
 - type AllocCount = Int64
 - type MemoHitCount = Int64
 - class (DataSourceName req, StateKey req, Show1 req) => DataSource u req 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 ())
 
 - newtype DataCache res = DataCache (HashMap TypeRep (SubCache res))
 - data SubCache res = (Hashable (req a), Eq (req a), Typeable (req a)) => SubCache (req a -> String) (a -> String) !(HashMap (req a) (res a))
 - emptyDataCache :: DataCache res
 - 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
 - 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 ()
 
Tracing flags
Flags that control the operation of the engine.
Constructors
| Flags | |
Fields  | |
defaultFlags :: Flags Source #
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.
Statistics
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  | 
Fields  | |
| FetchCall | The stack trace of a call to   | 
Fields 
  | |
Instances
data DataSourceRoundStats Source #
Detailed stats of each data source in each round.
Constructors
| DataSourceRoundStats | |
Fields  | |
Instances
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 #
Constructors
| ProfileData | |
Fields 
  | |
Instances
type AllocCount = Int64 Source #
type MemoHitCount = Int64 Source #
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
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
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 #
data BlockedFetch r Source #
A BlockedFetch is a pair of
- The request to fetch (with result type 
a) - A 
ResultVarto 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 anthat 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 anas an argument, which is the operation to perform while the data is being fetched.IO() 
See syncFetch and asyncFetch for example usage.
Constructors
| SyncFetch (IO ()) | |
| AsyncFetch (IO () -> IO ()) | 
DataCache
emptyDataCache :: DataCache res Source #
A new, empty DataCache.
Result variables
A sink for the result of a data fetch in BlockedFetch
Constructors
| 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
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 ystubFetch :: Exception e => (forall a. r a -> e) -> State r -> Flags -> u -> [BlockedFetch r] -> PerformFetch 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 |