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

Safe HaskellNone
LanguageHaskell2010

Haxl.Prelude

Contents

Description

Support for using Haxl as a DSL. This module provides most of the standard Prelude, plus a selection of stuff that makes Haxl client code cleaner and more concise.

We intend Haxl client code to:

  • Import Haxl.Prelude
  • Use RebindableSyntax. This implies NoImplicitPrelude, and allows if-then-else to be used with a monadic condition.
  • Use OverloadedStrings (we use Text a lot)

Synopsis

The Standard Haskell Prelude

Everything from Prelude except mapM, mapM_, sequence, and sequence

module Prelude

Haxl and Fetching data

data 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.

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 

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

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

class (DataSourceName req, StateKey req, Show1 req) => DataSource u req 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

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.

Extra Monad and Applicative things

class Functor f => Applicative f where

A functor with application, providing operations to

  • embed pure expressions (pure), and
  • sequence computations and combine their results (<*>).

A minimal complete definition must include implementations of these functions satisfying the following laws:

identity
pure id <*> v = v
composition
pure (.) <*> u <*> v <*> w = u <*> (v <*> w)
homomorphism
pure f <*> pure x = pure (f x)
interchange
u <*> pure y = pure ($ y) <*> u

The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:

As a consequence of these laws, the Functor instance for f will satisfy

If f is also a Monad, it should satisfy

(which implies that pure and <*> satisfy the applicative functor laws).

Minimal complete definition

pure, (<*>)

Methods

pure :: a -> f a

Lift a value.

(<*>) :: f (a -> b) -> f a -> f b infixl 4

Sequential application.

(*>) :: f a -> f b -> f b infixl 4

Sequence actions, discarding the value of the first argument.

(<*) :: f a -> f b -> f a infixl 4

Sequence actions, discarding the value of the second argument.

Instances

Applicative [] 
Applicative IO 
Applicative Q 
Applicative Maybe 
Applicative IResult 
Applicative Result 
Applicative Parser 
Applicative Id 
Applicative Identity 
Applicative ZipList 
Applicative STM 
Applicative First 
Applicative Last 
Applicative PutM 
Applicative Get 
Applicative Put 
Applicative Tree 
Applicative Seq 
Applicative DList 
Applicative Vector 
Applicative NonEmpty 
Applicative Id 
Applicative Box 
Applicative Option 
Applicative Min 
Applicative Max 
Applicative Last 
Applicative First 
Applicative ((->) a) 
Applicative (Either e) 
Monoid a => Applicative ((,) a) 
Applicative (ST s) 
Applicative (StateL s) 
Applicative (StateR s) 
Monoid m => Applicative (Const m) 
Monad m => Applicative (WrappedMonad m) 
Arrow a => Applicative (ArrowMonad a) 
Applicative (Proxy *) 
Applicative (State s) 
Applicative m => Applicative (ListT m) 
(Functor m, Monad m) => Applicative (MaybeT m) 
Applicative m => Applicative (IdentityT m) 
Monoid a => Applicative (Constant a) 
Applicative (Parser i) 
Applicative (GenHaxl u) 
Arrow a => Applicative (WrappedArrow a b) 
Applicative f => Applicative (Alt * f) 
Applicative (ContT r m) 
Applicative m => Applicative (ReaderT r m) 
(Functor m, Monad m) => Applicative (StateT s m) 
(Functor m, Monad m) => Applicative (StateT s m) 
(Functor m, Monad m) => Applicative (ExceptT e m) 
(Functor m, Monad m) => Applicative (ErrorT e m) 
(Monoid w, Applicative m) => Applicative (WriterT w m) 
(Monoid w, Applicative m) => Applicative (WriterT w m) 
Applicative (Tagged k s) 
(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) 
(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) 

mapM :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) Source

We don't want the monadic mapM, because that doesn't do batching. There doesn't seem to be a way to make mapM have the right behaviour when used with Haxl, so instead we define mapM to be traverse in Haxl code.

mapM_ :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f () Source

See mapM.

sequence :: (Traversable t, Applicative f) => t (f a) -> f (t a) Source

See mapM.

sequence_ :: (Traversable t, Applicative f) => t (f a) -> f () Source

See mapM.

filterM :: Applicative f => (a -> f Bool) -> [a] -> f [a] Source

See mapM.

foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b

The foldM function is analogous to foldl, except that its result is encapsulated in a monad. Note that foldM works from left-to-right over the list arguments. This could be an issue where (>>) and the `folded function' are not commutative.

      foldM f a1 [x1, x2, ..., xm]

==

      do
        a2 <- f a1 x1
        a3 <- f a2 x2
        ...
        f am xm

If right-to-left evaluation is required, the input list should be reversed.

Note: foldM is the same as foldlM

forM :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b) Source

forM_ :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f () Source

foldl' :: Foldable t => forall b a. (b -> a -> b) -> b -> t a -> b

Left-associative fold of a structure. but with strict application of the operator.

foldl f z = foldl' f z . toList

sort :: Ord a => [a] -> [a]

The sort function implements a stable sorting algorithm. It is a special case of sortBy, which allows the programmer to supply their own comparison function.

class Monoid a where

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

Minimal complete definition

mempty, mappend

Methods

mempty :: a

Identity of mappend

mappend :: a -> a -> a

An associative operation

mconcat :: [a] -> a

Fold a list using the monoid. For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

Instances

Monoid Ordering 
Monoid () 
Monoid ByteString 
Monoid ByteString 
Monoid Builder 
Monoid Encoding 
Monoid Series 
Monoid All 
Monoid Any 
Monoid ShortByteString 
Monoid IntSet 
Monoid Doc 
Monoid More 
Monoid Buffer 
Monoid Buffer 
Monoid [a] 
Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Monoid (IResult a) 
Monoid (Result a) 
Monoid (Parser a) 
Ord a => Monoid (Max a) 
Ord a => Monoid (Min a) 
Monoid a => Monoid (Dual a) 
Monoid (Endo a) 
Num a => Monoid (Sum a) 
Num a => Monoid (Product a) 
Monoid (First a) 
Monoid (Last a) 
Monoid (IntMap a) 
Ord a => Monoid (Set a) 
Monoid (Seq a) 
(Hashable a, Eq a) => Monoid (HashSet a) 
Monoid (DList a) 
Monoid (Vector a) 
Storable a => Monoid (Vector a) 
Prim a => Monoid (Vector a) 
Monoid m => Monoid (WrappedMonoid m) 
Semigroup a => Monoid (Option a) 
(Ord a, Bounded a) => Monoid (Min a) 
(Ord a, Bounded a) => Monoid (Max a) 
Monoid b => Monoid (a -> b) 
(Monoid a, Monoid b) => Monoid (a, b) 
(Eq k, Hashable k) => Monoid (HashMap k v) 
Ord k => Monoid (Map k v) 
Monoid a => Monoid (Const a b) 
Monoid (Proxy k s) 
Monoid (Parser i a) 
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 
Alternative f => Monoid (Alt * f a) 
Monoid a => Monoid (Tagged k s a) 
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) 
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) 

join :: Monad m => m (m a) -> m a

The join function is the conventional monad join operator. It is used to remove one level of monadic structure, projecting its bound argument into the outer level.

Lifted operations

class IfThenElse a b where Source

Methods

ifThenElse :: a -> b -> b -> b Source

Instances

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

(.>) :: Ord a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool infix 4 Source

(.<) :: Ord a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool infix 4 Source

(.>=) :: Ord a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool infix 4 Source

(.<=) :: Ord a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool infix 4 Source

(.==) :: Eq a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool infix 4 Source

(./=) :: Eq a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool infix 4 Source

(.&&) :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool infixr 3 Source

(.||) :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool infixr 2 Source

(.++) :: GenHaxl u [a] -> GenHaxl u [a] -> GenHaxl u [a] Source

pair :: GenHaxl u a -> GenHaxl u b -> GenHaxl u (a, b) Source

Text things

data Text :: *

Instances

Hashable Text 
Semigroup Text 
Chunk Text 
type Item Text = Char 
type State Text = Buffer 
type ChunkElem Text = Char 

class IsString a where

Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).

Methods

fromString :: String -> a

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

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.

withDefault :: a -> GenHaxl u a -> GenHaxl u a Source

Runs the given GenHaxl computation, and if it throws a TransientError or LogicError exception (see Haxl.Core.Exception), the exception is ignored and the supplied default value is returned instead.

catchAny Source

Arguments

:: GenHaxl u a

run this first

-> GenHaxl u a

if it throws LogicError or TransientError, run this

-> GenHaxl u a 

Catch LogicErrors and TransientErrors and perform an alternative action

data HaxlException Source

We have a 3-tiered hierarchy of exceptions, with HaxlException at the top, and all Haxl exceptions as children of this. Users should never deal directly with HaxlExceptions.

The main types of exceptions are:

InternalError
Something is wrong with Haxl core.
LogicBug
Something is wrong with Haxl client code.
LogicError
Things that really should be return values, e.g. NotFound.
TransientError
Something is temporarily failing (usually in a fetch).

These are not meant to be thrown (but likely be caught). Thrown exceptions should be a subclass of one of these. There are some generic leaf exceptions defined below this, such as FetchError (generic transient failure) or CriticalError (internal failure).

Constructors

forall e . MiddleException e => HaxlException (Maybe Stack) e 

Instances

Show HaxlException Source 
ToJSON HaxlException Source

These need to be serializable to JSON to cross FFI boundaries.

Exception HaxlException Source 

data LogicError Source

For errors in Haxl client code.

Constructors

forall e . Exception e => LogicError e 

newtype NotFound Source

Generic "something was not found" exception.

Constructors

NotFound Text 

newtype UnexpectedType Source

Generic "something had the wrong type" exception.

Constructors

UnexpectedType Text 

newtype FetchError Source

Generic transient fetching exceptions.

Constructors

FetchError Text 

newtype EmptyList Source

Generic "input list was empty" exception.

Constructors

EmptyList Text 

newtype InvalidParameter Source

Generic "passing some invalid parameter" exception.

Constructors

InvalidParameter Text